{-# LINE 1 "Graphics/X11/Xlib/Extras.hsc" #-}
{-# LANGUAGE DeriveDataTypeable #-}
-----------------------------------------------------------------------------
-- |
-- Module      : Graphics.X11.Xlib.Extras
-- Copyright   : 2007 (c) Spencer Janssen
-- License     : BSD3-style (see LICENSE)
-- Stability   : experimental
--
-----------------------------------------------------------------------------
--
-- missing functionality from the X11 library
--

module Graphics.X11.Xlib.Extras (
  module Graphics.X11.Xlib.Extras,
  module Graphics.X11.Xlib.Internal
  ) where

import Data.Maybe
import Data.Typeable ( Typeable )
import Graphics.X11.Xrandr
import Graphics.X11.XScreenSaver
import Graphics.X11.Xlib
import Graphics.X11.Xlib.Internal
import Graphics.X11.Xlib.Types
import Foreign (Storable, Ptr, peek, poke, pokeArray, peekElemOff, peekByteOff, pokeByteOff, peekArray, throwIfNull, nullPtr, sizeOf, alignment, alloca, with, throwIf, Word8, Word16, Word64, Int32, plusPtr, castPtr, withArrayLen, setBit, testBit, allocaBytes, FunPtr)
{-# LINE 27 "Graphics/X11/Xlib/Extras.hsc" #-}
import Foreign.C.Types
import Foreign.C.String
import Control.Monad

import System.IO.Unsafe



data Event
    = AnyEvent
        { Event -> EventType
ev_event_type            :: !EventType
        , Event -> CULong
ev_serial                :: !CULong
        , Event -> Bool
ev_send_event            :: !Bool
        , Event -> Display
ev_event_display         :: Display
        , Event -> Window
ev_window                :: !Window
        }
    | ConfigureRequestEvent
        { ev_event_type            :: !EventType
        , ev_serial                :: !CULong
        , ev_send_event            :: !Bool
        , ev_event_display         :: Display
        , Event -> Window
ev_parent                :: !Window
        , ev_window                :: !Window
        , Event -> CInt
ev_x                     :: !CInt
        , Event -> CInt
ev_y                     :: !CInt
        , Event -> CInt
ev_width                 :: !CInt
        , Event -> CInt
ev_height                :: !CInt
        , Event -> CInt
ev_border_width          :: !CInt
        , Event -> Window
ev_above                 :: !Window
        , Event -> CInt
ev_detail                :: !NotifyDetail
        , Event -> CULong
ev_value_mask            :: !CULong
        }
    | ConfigureEvent
        { ev_event_type            :: !EventType
        , ev_serial                :: !CULong
        , ev_send_event            :: !Bool
        , ev_event_display         :: Display
        , Event -> Window
ev_event                 :: !Window
        , ev_window                :: !Window
        , ev_x                     :: !CInt
        , ev_y                     :: !CInt
        , ev_width                 :: !CInt
        , ev_height                :: !CInt
        , ev_border_width          :: !CInt
        , ev_above                 :: !Window
        , Event -> Bool
ev_override_redirect     :: !Bool
        }
    | MapRequestEvent
        { ev_event_type            :: !EventType
        , ev_serial                :: !CULong
        , ev_send_event            :: !Bool
        , ev_event_display         :: Display
        , ev_parent                :: !Window
        , ev_window                :: !Window
        }
    | KeyEvent
        { ev_event_type            :: !EventType
        , ev_serial                :: !CULong
        , ev_send_event            :: !Bool
        , ev_event_display         :: Display
        , ev_window                :: !Window
        , Event -> Window
ev_root                  :: !Window
        , Event -> Window
ev_subwindow             :: !Window
        , Event -> Window
ev_time                  :: !Time
        , ev_x                     :: !CInt
        , ev_y                     :: !CInt
        , Event -> CInt
ev_x_root                :: !CInt
        , Event -> CInt
ev_y_root                :: !CInt
        , Event -> KeyMask
ev_state                 :: !KeyMask
        , Event -> KeyCode
ev_keycode               :: !KeyCode
        , Event -> Bool
ev_same_screen           :: !Bool
        }
    | ButtonEvent
        { ev_event_type            :: !EventType
        , ev_serial                :: !CULong
        , ev_send_event            :: !Bool
        , ev_event_display         :: Display
        , ev_window                :: !Window
        , ev_root                  :: !Window
        , ev_subwindow             :: !Window
        , ev_time                  :: !Time
        , ev_x                     :: !CInt
        , ev_y                     :: !CInt
        , ev_x_root                :: !CInt
        , ev_y_root                :: !CInt
        , ev_state                 :: !KeyMask
        , Event -> EventType
ev_button                :: !Button
        , ev_same_screen           :: !Bool
        }
    | MotionEvent
        { ev_event_type            :: !EventType
        , ev_serial                :: !CULong
        , ev_send_event            :: !Bool
        , ev_event_display         :: Display
        , ev_x                     :: !CInt
        , ev_y                     :: !CInt
        , ev_window                :: !Window
        }
    | DestroyWindowEvent
        { ev_event_type            :: !EventType
        , ev_serial                :: !CULong
        , ev_send_event            :: !Bool
        , ev_event_display         :: Display
        , ev_event                 :: !Window
        , ev_window                :: !Window
        }
    | UnmapEvent
        { ev_event_type            :: !EventType
        , ev_serial                :: !CULong
        , ev_send_event            :: !Bool
        , ev_event_display         :: Display
        , ev_event                 :: !Window
        , ev_window                :: !Window
        , Event -> Bool
ev_from_configure        :: !Bool
        }
    | MapNotifyEvent
        { ev_event_type            :: !EventType
        , ev_serial                :: !CULong
        , ev_send_event            :: !Bool
        , ev_event_display         :: Display
        , ev_event                 :: !Window
        , ev_window                :: !Window
        , ev_override_redirect     :: !Bool
        }
    | MappingNotifyEvent
        { ev_event_type            :: !EventType
        , ev_serial                :: !CULong
        , ev_send_event            :: !Bool
        , ev_event_display         :: Display
        , ev_window                :: !Window
        , Event -> CInt
ev_request               :: !MappingRequest
        , Event -> KeyCode
ev_first_keycode         :: !KeyCode
        , Event -> CInt
ev_count                 :: !CInt
        }
    | CrossingEvent
        { ev_event_type            :: !EventType
        , ev_serial                :: !CULong
        , ev_send_event            :: !Bool
        , ev_event_display         :: Display
        , ev_window                :: !Window
        , ev_root                  :: !Window
        , ev_subwindow             :: !Window
        , ev_time                  :: !Time
        , ev_x                     :: !CInt
        , ev_y                     :: !CInt
        , ev_x_root                :: !CInt
        , ev_y_root                :: !CInt
        , Event -> CInt
ev_mode                  :: !NotifyMode
        , ev_detail                :: !NotifyDetail
        , ev_same_screen           :: !Bool
        , Event -> Bool
ev_focus                 :: !Bool
        , ev_state                 :: !Modifier
        }
    | SelectionRequest
        { ev_event_type            :: !EventType
        , ev_serial                :: !CULong
        , ev_send_event            :: !Bool
        , ev_event_display         :: Display
        , Event -> Window
ev_owner                 :: !Window
        , Event -> Window
ev_requestor             :: !Window
        , Event -> Window
ev_selection             :: !Atom
        , Event -> Window
ev_target                :: !Atom
        , Event -> Window
ev_property              :: !Atom
        , ev_time                  :: !Time
        }
    | SelectionClear
        { ev_event_type            :: !EventType
        , ev_serial                :: !CULong
        , ev_send_event            :: !Bool
        , ev_event_display         :: Display
        , ev_window                :: !Window
        , ev_selection             :: !Atom
        , ev_time                  :: !Time
        }
    | PropertyEvent
        { ev_event_type            :: !EventType
        , ev_serial                :: !CULong
        , ev_send_event            :: !Bool
        , ev_event_display         :: Display
        , ev_window                :: !Window
        , Event -> Window
ev_atom                  :: !Atom
        , ev_time                  :: !Time
        , Event -> CInt
ev_propstate             :: !CInt
        }
    | ExposeEvent
        { ev_event_type            :: !EventType
        , ev_serial                :: !CULong
        , ev_send_event            :: !Bool
        , ev_event_display         :: Display
        , ev_window                :: !Window
        , ev_x                     :: !CInt
        , ev_y                     :: !CInt
        , ev_width                 :: !CInt
        , ev_height                :: !CInt
        , ev_count                 :: !CInt
        }
    | ClientMessageEvent
        { ev_event_type            :: !EventType
        , ev_serial                :: !CULong
        , ev_send_event            :: !Bool
        , ev_event_display         :: Display
        , ev_window                :: !Window
        , Event -> Window
ev_message_type          :: !Atom
        , Event -> [CInt]
ev_data                  :: ![CInt]
        }
    | RRScreenChangeNotifyEvent
        { ev_event_type            :: !EventType
        , ev_serial                :: !CULong
        , ev_send_event            :: !Bool
        , ev_event_display         :: Display
        , ev_window                :: !Window
        , ev_root                  :: !Window
        , Event -> Window
ev_timestamp             :: !Time
        , Event -> Window
ev_config_timestamp      :: !Time
        , Event -> SizeID
ev_size_index            :: !SizeID
        , Event -> SizeID
ev_subpixel_order        :: !SubpixelOrder
        , Event -> SizeID
ev_rotation              :: !Rotation
        , ev_width                 :: !CInt
        , ev_height                :: !CInt
        , Event -> CInt
ev_mwidth                :: !CInt
        , Event -> CInt
ev_mheight               :: !CInt
        }
    | RRNotifyEvent
        { ev_event_type            :: !EventType
        , ev_serial                :: !CULong
        , ev_send_event            :: !Bool
        , ev_event_display         :: Display
        , ev_window                :: !Window
        , Event -> CInt
ev_subtype               :: !CInt
        }
    | RRCrtcChangeNotifyEvent
        { ev_event_type            :: !EventType
        , ev_serial                :: !CULong
        , ev_send_event            :: !Bool
        , ev_event_display         :: Display
        , ev_window                :: !Window
        , ev_subtype               :: !CInt
        , Event -> Window
ev_crtc                  :: !RRCrtc
        , Event -> Window
ev_rr_mode               :: !RRMode
        , ev_rotation              :: !Rotation
        , ev_x                     :: !CInt
        , ev_y                     :: !CInt
        , Event -> KeyMask
ev_rr_width              :: !CUInt
        , Event -> KeyMask
ev_rr_height             :: !CUInt
        }
    | RROutputChangeNotifyEvent
        { ev_event_type            :: !EventType
        , ev_serial                :: !CULong
        , ev_send_event            :: !Bool
        , ev_event_display         :: Display
        , ev_window                :: !Window
        , ev_subtype               :: !CInt
        , Event -> Window
ev_output                :: !RROutput
        , ev_crtc                  :: !RRCrtc
        , ev_rr_mode               :: !RRMode
        , ev_rotation              :: !Rotation
        , Event -> SizeID
ev_connection            :: !Connection
        , ev_subpixel_order        :: !SubpixelOrder
        }
    | RROutputPropertyNotifyEvent
        { ev_event_type            :: !EventType
        , ev_serial                :: !CULong
        , ev_send_event            :: !Bool
        , ev_event_display         :: Display
        , ev_window                :: !Window
        , ev_subtype               :: !CInt
        , ev_output                :: !RROutput
        , ev_property              :: !Atom
        , ev_timestamp             :: !Time
        , Event -> CInt
ev_rr_state              :: !CInt
        }
    | ScreenSaverNotifyEvent
        { ev_event_type            :: !EventType
        , ev_serial                :: !CULong
        , ev_send_event            :: !Bool
        , ev_event_display         :: Display
        , ev_window                :: !Window
        , ev_root                  :: !Window
        , Event -> XScreenSaverState
ev_ss_state              :: !XScreenSaverState
        , Event -> XScreenSaverKind
ev_ss_kind               :: !XScreenSaverKind
        , Event -> Bool
ev_forced                :: !Bool
        , ev_time                  :: !Time
        }
    deriving ( Int -> Event -> ShowS
[Event] -> ShowS
Event -> String
(Int -> Event -> ShowS)
-> (Event -> String) -> ([Event] -> ShowS) -> Show Event
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Event] -> ShowS
$cshowList :: [Event] -> ShowS
show :: Event -> String
$cshow :: Event -> String
showsPrec :: Int -> Event -> ShowS
$cshowsPrec :: Int -> Event -> ShowS
Show, Typeable )

eventTable :: [(EventType, String)]
eventTable :: [(EventType, String)]
eventTable =
    [ (EventType
keyPress             , String
"KeyPress")
    , (EventType
keyRelease           , String
"KeyRelease")
    , (EventType
buttonPress          , String
"ButtonPress")
    , (EventType
buttonRelease        , String
"ButtonRelease")
    , (EventType
motionNotify         , String
"MotionNotify")
    , (EventType
enterNotify          , String
"EnterNotify")
    , (EventType
leaveNotify          , String
"LeaveNotify")
    , (EventType
focusIn              , String
"FocusIn")
    , (EventType
focusOut             , String
"FocusOut")
    , (EventType
keymapNotify         , String
"KeymapNotify")
    , (EventType
expose               , String
"Expose")
    , (EventType
graphicsExpose       , String
"GraphicsExpose")
    , (EventType
noExpose             , String
"NoExpose")
    , (EventType
visibilityNotify     , String
"VisibilityNotify")
    , (EventType
createNotify         , String
"CreateNotify")
    , (EventType
destroyNotify        , String
"DestroyNotify")
    , (EventType
unmapNotify          , String
"UnmapNotify")
    , (EventType
mapNotify            , String
"MapNotify")
    , (EventType
mapRequest           , String
"MapRequest")
    , (EventType
reparentNotify       , String
"ReparentNotify")
    , (EventType
configureNotify      , String
"ConfigureNotify")
    , (EventType
configureRequest     , String
"ConfigureRequest")
    , (EventType
gravityNotify        , String
"GravityNotify")
    , (EventType
resizeRequest        , String
"ResizeRequest")
    , (EventType
circulateNotify      , String
"CirculateNotify")
    , (EventType
circulateRequest     , String
"CirculateRequest")
    , (EventType
propertyNotify       , String
"PropertyNotify")
    , (EventType
selectionClear       , String
"SelectionClear")
    , (EventType
selectionRequest     , String
"SelectionRequest")
    , (EventType
selectionNotify      , String
"SelectionNotify")
    , (EventType
colormapNotify       , String
"ColormapNotify")
    , (EventType
clientMessage        , String
"ClientMessage")
    , (EventType
mappingNotify        , String
"MappingNotify")
    , (EventType
lASTEvent            , String
"LASTEvent")
    , (EventType
screenSaverNotify    , String
"ScreenSaverNotify")
    ]

eventName :: Event -> String
eventName :: Event -> String
eventName Event
e = String -> ShowS -> Maybe String -> String
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (String
"unknown " String -> ShowS
forall a. [a] -> [a] -> [a]
++ EventType -> String
forall a. Show a => a -> String
show EventType
x) ShowS
forall a. a -> a
id (Maybe String -> String) -> Maybe String -> String
forall a b. (a -> b) -> a -> b
$ EventType -> [(EventType, String)] -> Maybe String
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup EventType
x [(EventType, String)]
eventTable
 where x :: EventType
x = EventType -> EventType
forall a b. (Integral a, Num b) => a -> b
fromIntegral (EventType -> EventType) -> EventType -> EventType
forall a b. (a -> b) -> a -> b
$ Event -> EventType
ev_event_type Event
e

getEvent :: XEventPtr -> IO Event
getEvent :: XEventPtr -> IO Event
getEvent XEventPtr
p = do
    -- All events share this layout and naming convention, there is also a
    -- common Window field, but the names for this field vary.
    EventType
type_      <- (\XEventPtr
hsc_ptr -> XEventPtr -> Int -> IO EventType
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff XEventPtr
hsc_ptr Int
0) XEventPtr
p
{-# LINE 360 "Graphics/X11/Xlib/Extras.hsc" #-}
    serial     <- (\hsc_ptr -> peekByteOff hsc_ptr 8) p
{-# LINE 361 "Graphics/X11/Xlib/Extras.hsc" #-}
    send_event <- (\hsc_ptr -> peekByteOff hsc_ptr 16) p
{-# LINE 362 "Graphics/X11/Xlib/Extras.hsc" #-}
    display    <- fmap Display ((\hsc_ptr -> peekByteOff hsc_ptr 24) p)
{-# LINE 363 "Graphics/X11/Xlib/Extras.hsc" #-}
    rrData     <- xrrQueryExtension display
    let rrHasExtension :: Bool
rrHasExtension = Maybe (CInt, CInt) -> Bool
forall a. Maybe a -> Bool
isJust Maybe (CInt, CInt)
rrData
    let rrEventBase :: EventType
rrEventBase    = CInt -> EventType
forall a b. (Integral a, Num b) => a -> b
fromIntegral (CInt -> EventType) -> CInt -> EventType
forall a b. (a -> b) -> a -> b
$ (CInt, CInt) -> CInt
forall a b. (a, b) -> a
fst ((CInt, CInt) -> CInt) -> (CInt, CInt) -> CInt
forall a b. (a -> b) -> a -> b
$ (CInt, CInt) -> Maybe (CInt, CInt) -> (CInt, CInt)
forall a. a -> Maybe a -> a
fromMaybe (CInt
0, CInt
0) Maybe (CInt, CInt)
rrData
    case () of

        -------------------------
        -- ConfigureRequestEvent:
        -------------------------
        ()
_ | EventType
type_ EventType -> EventType -> Bool
forall a. Eq a => a -> a -> Bool
== EventType
configureRequest -> do
            Window
parent       <- (\XEventPtr
hsc_ptr -> XEventPtr -> Int -> IO Window
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff XEventPtr
hsc_ptr Int
32) XEventPtr
p
{-# LINE 373 "Graphics/X11/Xlib/Extras.hsc" #-}
            Window
window       <- (\XEventPtr
hsc_ptr -> XEventPtr -> Int -> IO Window
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff XEventPtr
hsc_ptr Int
40) XEventPtr
p
{-# LINE 374 "Graphics/X11/Xlib/Extras.hsc" #-}
            CInt
x            <- (\XEventPtr
hsc_ptr -> XEventPtr -> Int -> IO CInt
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff XEventPtr
hsc_ptr Int
48) XEventPtr
p
{-# LINE 375 "Graphics/X11/Xlib/Extras.hsc" #-}
            CInt
y            <- (\XEventPtr
hsc_ptr -> XEventPtr -> Int -> IO CInt
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff XEventPtr
hsc_ptr Int
52) XEventPtr
p
{-# LINE 376 "Graphics/X11/Xlib/Extras.hsc" #-}
            CInt
width        <- (\XEventPtr
hsc_ptr -> XEventPtr -> Int -> IO CInt
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff XEventPtr
hsc_ptr Int
56) XEventPtr
p
{-# LINE 377 "Graphics/X11/Xlib/Extras.hsc" #-}
            CInt
height       <- (\XEventPtr
hsc_ptr -> XEventPtr -> Int -> IO CInt
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff XEventPtr
hsc_ptr Int
60) XEventPtr
p
{-# LINE 378 "Graphics/X11/Xlib/Extras.hsc" #-}
            CInt
border_width <- (\XEventPtr
hsc_ptr -> XEventPtr -> Int -> IO CInt
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff XEventPtr
hsc_ptr Int
64) XEventPtr
p
{-# LINE 379 "Graphics/X11/Xlib/Extras.hsc" #-}
            Window
above        <- (\XEventPtr
hsc_ptr -> XEventPtr -> Int -> IO Window
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff XEventPtr
hsc_ptr Int
72) XEventPtr
p
{-# LINE 380 "Graphics/X11/Xlib/Extras.hsc" #-}
            CInt
detail       <- (\XEventPtr
hsc_ptr -> XEventPtr -> Int -> IO CInt
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff XEventPtr
hsc_ptr Int
80) XEventPtr
p
{-# LINE 381 "Graphics/X11/Xlib/Extras.hsc" #-}
            CULong
value_mask   <- (\XEventPtr
hsc_ptr -> XEventPtr -> Int -> IO CULong
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff XEventPtr
hsc_ptr Int
88) XEventPtr
p
{-# LINE 382 "Graphics/X11/Xlib/Extras.hsc" #-}
            Event -> IO Event
forall (m :: * -> *) a. Monad m => a -> m a
return (Event -> IO Event) -> Event -> IO Event
forall a b. (a -> b) -> a -> b
$ ConfigureRequestEvent :: EventType
-> CULong
-> Bool
-> Display
-> Window
-> Window
-> CInt
-> CInt
-> CInt
-> CInt
-> CInt
-> Window
-> CInt
-> CULong
-> Event
ConfigureRequestEvent
                        { ev_event_type :: EventType
ev_event_type    = EventType
type_
                        , ev_serial :: CULong
ev_serial        = CULong
serial
                        , ev_send_event :: Bool
ev_send_event    = Bool
send_event
                        , ev_event_display :: Display
ev_event_display = Display
display
                        , ev_parent :: Window
ev_parent        = Window
parent
                        , ev_window :: Window
ev_window        = Window
window
                        , ev_x :: CInt
ev_x             = CInt
x
                        , ev_y :: CInt
ev_y             = CInt
y
                        , ev_width :: CInt
ev_width         = CInt
width
                        , ev_height :: CInt
ev_height        = CInt
height
                        , ev_border_width :: CInt
ev_border_width  = CInt
border_width
                        , ev_above :: Window
ev_above         = Window
above
                        , ev_detail :: CInt
ev_detail        = CInt
detail
                        , ev_value_mask :: CULong
ev_value_mask    = CULong
value_mask
                        }

          ------------------
          -- ConfigureEvent:
          ------------------
          | EventType
type_ EventType -> EventType -> Bool
forall a. Eq a => a -> a -> Bool
== EventType
configureNotify -> do
            (Window
 -> Window
 -> CInt
 -> CInt
 -> CInt
 -> CInt
 -> CInt
 -> Window
 -> Bool
 -> Event)
-> IO
     (Window
      -> Window
      -> CInt
      -> CInt
      -> CInt
      -> CInt
      -> CInt
      -> Window
      -> Bool
      -> Event)
forall (m :: * -> *) a. Monad m => a -> m a
return (EventType
-> CULong
-> Bool
-> Display
-> Window
-> Window
-> CInt
-> CInt
-> CInt
-> CInt
-> CInt
-> Window
-> Bool
-> Event
ConfigureEvent EventType
type_ CULong
serial Bool
send_event Display
display)
                IO
  (Window
   -> Window
   -> CInt
   -> CInt
   -> CInt
   -> CInt
   -> CInt
   -> Window
   -> Bool
   -> Event)
-> IO Window
-> IO
     (Window
      -> CInt -> CInt -> CInt -> CInt -> CInt -> Window -> Bool -> Event)
forall (m :: * -> *) a b. Monad m => m (a -> b) -> m a -> m b
`ap` (\XEventPtr
hsc_ptr -> XEventPtr -> Int -> IO Window
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff XEventPtr
hsc_ptr Int
32) XEventPtr
p
{-# LINE 405 "Graphics/X11/Xlib/Extras.hsc" #-}
                IO
  (Window
   -> CInt -> CInt -> CInt -> CInt -> CInt -> Window -> Bool -> Event)
-> IO Window
-> IO
     (CInt -> CInt -> CInt -> CInt -> CInt -> Window -> Bool -> Event)
forall (m :: * -> *) a b. Monad m => m (a -> b) -> m a -> m b
`ap` (\XEventPtr
hsc_ptr -> XEventPtr -> Int -> IO Window
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff XEventPtr
hsc_ptr Int
40) XEventPtr
p
{-# LINE 406 "Graphics/X11/Xlib/Extras.hsc" #-}
                IO
  (CInt -> CInt -> CInt -> CInt -> CInt -> Window -> Bool -> Event)
-> IO CInt
-> IO (CInt -> CInt -> CInt -> CInt -> Window -> Bool -> Event)
forall (m :: * -> *) a b. Monad m => m (a -> b) -> m a -> m b
`ap` (\XEventPtr
hsc_ptr -> XEventPtr -> Int -> IO CInt
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff XEventPtr
hsc_ptr Int
48) XEventPtr
p
{-# LINE 407 "Graphics/X11/Xlib/Extras.hsc" #-}
                IO (CInt -> CInt -> CInt -> CInt -> Window -> Bool -> Event)
-> IO CInt -> IO (CInt -> CInt -> CInt -> Window -> Bool -> Event)
forall (m :: * -> *) a b. Monad m => m (a -> b) -> m a -> m b
`ap` (\XEventPtr
hsc_ptr -> XEventPtr -> Int -> IO CInt
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff XEventPtr
hsc_ptr Int
52) XEventPtr
p
{-# LINE 408 "Graphics/X11/Xlib/Extras.hsc" #-}
                IO (CInt -> CInt -> CInt -> Window -> Bool -> Event)
-> IO CInt -> IO (CInt -> CInt -> Window -> Bool -> Event)
forall (m :: * -> *) a b. Monad m => m (a -> b) -> m a -> m b
`ap` (\XEventPtr
hsc_ptr -> XEventPtr -> Int -> IO CInt
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff XEventPtr
hsc_ptr Int
56) XEventPtr
p
{-# LINE 409 "Graphics/X11/Xlib/Extras.hsc" #-}
                IO (CInt -> CInt -> Window -> Bool -> Event)
-> IO CInt -> IO (CInt -> Window -> Bool -> Event)
forall (m :: * -> *) a b. Monad m => m (a -> b) -> m a -> m b
`ap` (\XEventPtr
hsc_ptr -> XEventPtr -> Int -> IO CInt
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff XEventPtr
hsc_ptr Int
60) XEventPtr
p
{-# LINE 410 "Graphics/X11/Xlib/Extras.hsc" #-}
                IO (CInt -> Window -> Bool -> Event)
-> IO CInt -> IO (Window -> Bool -> Event)
forall (m :: * -> *) a b. Monad m => m (a -> b) -> m a -> m b
`ap` (\XEventPtr
hsc_ptr -> XEventPtr -> Int -> IO CInt
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff XEventPtr
hsc_ptr Int
64) XEventPtr
p
{-# LINE 411 "Graphics/X11/Xlib/Extras.hsc" #-}
                IO (Window -> Bool -> Event) -> IO Window -> IO (Bool -> Event)
forall (m :: * -> *) a b. Monad m => m (a -> b) -> m a -> m b
`ap` (\XEventPtr
hsc_ptr -> XEventPtr -> Int -> IO Window
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff XEventPtr
hsc_ptr Int
72) XEventPtr
p
{-# LINE 412 "Graphics/X11/Xlib/Extras.hsc" #-}
                IO (Bool -> Event) -> IO Bool -> IO Event
forall (m :: * -> *) a b. Monad m => m (a -> b) -> m a -> m b
`ap` (\XEventPtr
hsc_ptr -> XEventPtr -> Int -> IO Bool
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff XEventPtr
hsc_ptr Int
80) XEventPtr
p
{-# LINE 413 "Graphics/X11/Xlib/Extras.hsc" #-}

          -------------------
          -- MapRequestEvent:
          -------------------
          | EventType
type_ EventType -> EventType -> Bool
forall a. Eq a => a -> a -> Bool
== EventType
mapRequest -> do
            Window
parent <- (\XEventPtr
hsc_ptr -> XEventPtr -> Int -> IO Window
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff XEventPtr
hsc_ptr Int
32) XEventPtr
p
{-# LINE 419 "Graphics/X11/Xlib/Extras.hsc" #-}
            Window
window <- (\XEventPtr
hsc_ptr -> XEventPtr -> Int -> IO Window
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff XEventPtr
hsc_ptr Int
40) XEventPtr
p
{-# LINE 420 "Graphics/X11/Xlib/Extras.hsc" #-}
            Event -> IO Event
forall (m :: * -> *) a. Monad m => a -> m a
return (Event -> IO Event) -> Event -> IO Event
forall a b. (a -> b) -> a -> b
$ MapRequestEvent :: EventType -> CULong -> Bool -> Display -> Window -> Window -> Event
MapRequestEvent
                        { ev_event_type :: EventType
ev_event_type    = EventType
type_
                        , ev_serial :: CULong
ev_serial        = CULong
serial
                        , ev_send_event :: Bool
ev_send_event    = Bool
send_event
                        , ev_event_display :: Display
ev_event_display = Display
display
                        , ev_parent :: Window
ev_parent        = Window
parent
                        , ev_window :: Window
ev_window        = Window
window
                        }

          -------------------
          -- MapNotifyEvent
          -------------------
          | EventType
type_ EventType -> EventType -> Bool
forall a. Eq a => a -> a -> Bool
== EventType
mapNotify -> do
            Window
event             <- (\XEventPtr
hsc_ptr -> XEventPtr -> Int -> IO Window
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff XEventPtr
hsc_ptr Int
32)  XEventPtr
p
{-# LINE 434 "Graphics/X11/Xlib/Extras.hsc" #-}
            Window
window            <- (\XEventPtr
hsc_ptr -> XEventPtr -> Int -> IO Window
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff XEventPtr
hsc_ptr Int
40) XEventPtr
p
{-# LINE 435 "Graphics/X11/Xlib/Extras.hsc" #-}
            Bool
override_redirect <- (\XEventPtr
hsc_ptr -> XEventPtr -> Int -> IO Bool
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff XEventPtr
hsc_ptr Int
48) XEventPtr
p
{-# LINE 436 "Graphics/X11/Xlib/Extras.hsc" #-}
            Event -> IO Event
forall (m :: * -> *) a. Monad m => a -> m a
return (Event -> IO Event) -> Event -> IO Event
forall a b. (a -> b) -> a -> b
$ MapNotifyEvent :: EventType
-> CULong -> Bool -> Display -> Window -> Window -> Bool -> Event
MapNotifyEvent
                        { ev_event_type :: EventType
ev_event_type        = EventType
type_
                        , ev_serial :: CULong
ev_serial            = CULong
serial
                        , ev_send_event :: Bool
ev_send_event        = Bool
send_event
                        , ev_event_display :: Display
ev_event_display     = Display
display
                        , ev_event :: Window
ev_event             = Window
event
                        , ev_window :: Window
ev_window            = Window
window
                        , ev_override_redirect :: Bool
ev_override_redirect = Bool
override_redirect
                        }

          -------------------
          -- MappingNotifyEvent
          -------------------
          | EventType
type_ EventType -> EventType -> Bool
forall a. Eq a => a -> a -> Bool
== EventType
mappingNotify -> do
            Window
window        <- (\XEventPtr
hsc_ptr -> XEventPtr -> Int -> IO Window
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff XEventPtr
hsc_ptr Int
32)          XEventPtr
p
{-# LINE 451 "Graphics/X11/Xlib/Extras.hsc" #-}
            CInt
request       <- (\XEventPtr
hsc_ptr -> XEventPtr -> Int -> IO CInt
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff XEventPtr
hsc_ptr Int
40)         XEventPtr
p
{-# LINE 452 "Graphics/X11/Xlib/Extras.hsc" #-}
            KeyCode
first_keycode <- (\XEventPtr
hsc_ptr -> XEventPtr -> Int -> IO KeyCode
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff XEventPtr
hsc_ptr Int
44)   XEventPtr
p
{-# LINE 453 "Graphics/X11/Xlib/Extras.hsc" #-}
            CInt
count         <- (\XEventPtr
hsc_ptr -> XEventPtr -> Int -> IO CInt
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff XEventPtr
hsc_ptr Int
48)           XEventPtr
p
{-# LINE 454 "Graphics/X11/Xlib/Extras.hsc" #-}

            Event -> IO Event
forall (m :: * -> *) a. Monad m => a -> m a
return (Event -> IO Event) -> Event -> IO Event
forall a b. (a -> b) -> a -> b
$ MappingNotifyEvent :: EventType
-> CULong
-> Bool
-> Display
-> Window
-> CInt
-> KeyCode
-> CInt
-> Event
MappingNotifyEvent
                        { ev_event_type :: EventType
ev_event_type    = EventType
type_
                        , ev_serial :: CULong
ev_serial        = CULong
serial
                        , ev_send_event :: Bool
ev_send_event    = Bool
send_event
                        , ev_event_display :: Display
ev_event_display = Display
display
                        , ev_window :: Window
ev_window        = Window
window
                        , ev_request :: CInt
ev_request       = CInt
request
                        , ev_first_keycode :: KeyCode
ev_first_keycode = KeyCode
first_keycode
                        , ev_count :: CInt
ev_count         = CInt
count
                        }

          ------------
          -- KeyEvent:
          ------------
          | EventType
type_ EventType -> EventType -> Bool
forall a. Eq a => a -> a -> Bool
== EventType
keyPress Bool -> Bool -> Bool
|| EventType
type_ EventType -> EventType -> Bool
forall a. Eq a => a -> a -> Bool
== EventType
keyRelease -> do
            Window
window      <- (\XEventPtr
hsc_ptr -> XEventPtr -> Int -> IO Window
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff XEventPtr
hsc_ptr Int
32) XEventPtr
p
{-# LINE 471 "Graphics/X11/Xlib/Extras.hsc" #-}
            Window
root        <- (\XEventPtr
hsc_ptr -> XEventPtr -> Int -> IO Window
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff XEventPtr
hsc_ptr Int
40) XEventPtr
p
{-# LINE 472 "Graphics/X11/Xlib/Extras.hsc" #-}
            Window
subwindow   <- (\XEventPtr
hsc_ptr -> XEventPtr -> Int -> IO Window
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff XEventPtr
hsc_ptr Int
48) XEventPtr
p
{-# LINE 473 "Graphics/X11/Xlib/Extras.hsc" #-}
            Window
time        <- (\XEventPtr
hsc_ptr -> XEventPtr -> Int -> IO Window
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff XEventPtr
hsc_ptr Int
56) XEventPtr
p
{-# LINE 474 "Graphics/X11/Xlib/Extras.hsc" #-}
            CInt
x           <- (\XEventPtr
hsc_ptr -> XEventPtr -> Int -> IO CInt
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff XEventPtr
hsc_ptr Int
64) XEventPtr
p
{-# LINE 475 "Graphics/X11/Xlib/Extras.hsc" #-}
            CInt
y           <- (\XEventPtr
hsc_ptr -> XEventPtr -> Int -> IO CInt
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff XEventPtr
hsc_ptr Int
68) XEventPtr
p
{-# LINE 476 "Graphics/X11/Xlib/Extras.hsc" #-}
            CInt
x_root      <- (\XEventPtr
hsc_ptr -> XEventPtr -> Int -> IO CInt
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff XEventPtr
hsc_ptr Int
72) XEventPtr
p
{-# LINE 477 "Graphics/X11/Xlib/Extras.hsc" #-}
            CInt
y_root      <- (\XEventPtr
hsc_ptr -> XEventPtr -> Int -> IO CInt
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff XEventPtr
hsc_ptr Int
76) XEventPtr
p
{-# LINE 478 "Graphics/X11/Xlib/Extras.hsc" #-}
            KeyMask
state       <- ((\XEventPtr
hsc_ptr -> XEventPtr -> Int -> IO KeyMask
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff XEventPtr
hsc_ptr Int
80) XEventPtr
p) :: IO CUInt
{-# LINE 479 "Graphics/X11/Xlib/Extras.hsc" #-}
            KeyMask
keycode     <- ((\XEventPtr
hsc_ptr -> XEventPtr -> Int -> IO KeyMask
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff XEventPtr
hsc_ptr Int
84) XEventPtr
p) :: IO CUInt
{-# LINE 480 "Graphics/X11/Xlib/Extras.hsc" #-}
            Bool
same_screen <- (\XEventPtr
hsc_ptr -> XEventPtr -> Int -> IO Bool
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff XEventPtr
hsc_ptr Int
88) XEventPtr
p
{-# LINE 481 "Graphics/X11/Xlib/Extras.hsc" #-}
            Event -> IO Event
forall (m :: * -> *) a. Monad m => a -> m a
return (Event -> IO Event) -> Event -> IO Event
forall a b. (a -> b) -> a -> b
$ KeyEvent :: EventType
-> CULong
-> Bool
-> Display
-> Window
-> Window
-> Window
-> Window
-> CInt
-> CInt
-> CInt
-> CInt
-> KeyMask
-> KeyCode
-> Bool
-> Event
KeyEvent
                        { ev_event_type :: EventType
ev_event_type    = EventType
type_
                        , ev_serial :: CULong
ev_serial        = CULong
serial
                        , ev_send_event :: Bool
ev_send_event    = Bool
send_event
                        , ev_event_display :: Display
ev_event_display = Display
display
                        , ev_window :: Window
ev_window        = Window
window
                        , ev_root :: Window
ev_root          = Window
root
                        , ev_subwindow :: Window
ev_subwindow     = Window
subwindow
                        , ev_time :: Window
ev_time          = Window
time
                        , ev_x :: CInt
ev_x             = CInt
x
                        , ev_y :: CInt
ev_y             = CInt
y
                        , ev_x_root :: CInt
ev_x_root        = CInt
x_root
                        , ev_y_root :: CInt
ev_y_root        = CInt
y_root
                        , ev_state :: KeyMask
ev_state         = KeyMask -> KeyMask
forall a b. (Integral a, Num b) => a -> b
fromIntegral KeyMask
state
                        , ev_keycode :: KeyCode
ev_keycode       = KeyMask -> KeyCode
forall a b. (Integral a, Num b) => a -> b
fromIntegral KeyMask
keycode
                        , ev_same_screen :: Bool
ev_same_screen   = Bool
same_screen
                        }

          ---------------
          -- ButtonEvent:
          ---------------
          | EventType
type_ EventType -> EventType -> Bool
forall a. Eq a => a -> a -> Bool
== EventType
buttonPress Bool -> Bool -> Bool
|| EventType
type_ EventType -> EventType -> Bool
forall a. Eq a => a -> a -> Bool
== EventType
buttonRelease -> do

            Window
window      <- (\XEventPtr
hsc_ptr -> XEventPtr -> Int -> IO Window
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff XEventPtr
hsc_ptr Int
32) XEventPtr
p
{-# LINE 505 "Graphics/X11/Xlib/Extras.hsc" #-}
            Window
root        <- (\XEventPtr
hsc_ptr -> XEventPtr -> Int -> IO Window
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff XEventPtr
hsc_ptr Int
40) XEventPtr
p
{-# LINE 506 "Graphics/X11/Xlib/Extras.hsc" #-}
            Window
subwindow   <- (\XEventPtr
hsc_ptr -> XEventPtr -> Int -> IO Window
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff XEventPtr
hsc_ptr Int
48) XEventPtr
p
{-# LINE 507 "Graphics/X11/Xlib/Extras.hsc" #-}
            Window
time        <- (\XEventPtr
hsc_ptr -> XEventPtr -> Int -> IO Window
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff XEventPtr
hsc_ptr Int
56) XEventPtr
p
{-# LINE 508 "Graphics/X11/Xlib/Extras.hsc" #-}
            CInt
x           <- (\XEventPtr
hsc_ptr -> XEventPtr -> Int -> IO CInt
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff XEventPtr
hsc_ptr Int
64) XEventPtr
p
{-# LINE 509 "Graphics/X11/Xlib/Extras.hsc" #-}
            CInt
y           <- (\XEventPtr
hsc_ptr -> XEventPtr -> Int -> IO CInt
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff XEventPtr
hsc_ptr Int
68) XEventPtr
p
{-# LINE 510 "Graphics/X11/Xlib/Extras.hsc" #-}
            CInt
x_root      <- (\XEventPtr
hsc_ptr -> XEventPtr -> Int -> IO CInt
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff XEventPtr
hsc_ptr Int
72) XEventPtr
p
{-# LINE 511 "Graphics/X11/Xlib/Extras.hsc" #-}
            CInt
y_root      <- (\XEventPtr
hsc_ptr -> XEventPtr -> Int -> IO CInt
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff XEventPtr
hsc_ptr Int
76) XEventPtr
p
{-# LINE 512 "Graphics/X11/Xlib/Extras.hsc" #-}
            KeyMask
state       <- ((\XEventPtr
hsc_ptr -> XEventPtr -> Int -> IO KeyMask
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff XEventPtr
hsc_ptr Int
80) XEventPtr
p) :: IO CUInt
{-# LINE 513 "Graphics/X11/Xlib/Extras.hsc" #-}
            EventType
button      <- (\XEventPtr
hsc_ptr -> XEventPtr -> Int -> IO EventType
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff XEventPtr
hsc_ptr Int
84) XEventPtr
p
{-# LINE 514 "Graphics/X11/Xlib/Extras.hsc" #-}
            Bool
same_screen <- (\XEventPtr
hsc_ptr -> XEventPtr -> Int -> IO Bool
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff XEventPtr
hsc_ptr Int
88) XEventPtr
p
{-# LINE 515 "Graphics/X11/Xlib/Extras.hsc" #-}

            Event -> IO Event
forall (m :: * -> *) a. Monad m => a -> m a
return (Event -> IO Event) -> Event -> IO Event
forall a b. (a -> b) -> a -> b
$ ButtonEvent :: EventType
-> CULong
-> Bool
-> Display
-> Window
-> Window
-> Window
-> Window
-> CInt
-> CInt
-> CInt
-> CInt
-> KeyMask
-> EventType
-> Bool
-> Event
ButtonEvent
                        { ev_event_type :: EventType
ev_event_type    = EventType
type_
                        , ev_serial :: CULong
ev_serial        = CULong
serial
                        , ev_send_event :: Bool
ev_send_event    = Bool
send_event
                        , ev_event_display :: Display
ev_event_display = Display
display
                        , ev_window :: Window
ev_window        = Window
window
                        , ev_root :: Window
ev_root          = Window
root
                        , ev_subwindow :: Window
ev_subwindow     = Window
subwindow
                        , ev_time :: Window
ev_time          = Window
time
                        , ev_x :: CInt
ev_x             = CInt
x
                        , ev_y :: CInt
ev_y             = CInt
y
                        , ev_x_root :: CInt
ev_x_root        = CInt
x_root
                        , ev_y_root :: CInt
ev_y_root        = CInt
y_root
                        , ev_state :: KeyMask
ev_state         = KeyMask -> KeyMask
forall a b. (Integral a, Num b) => a -> b
fromIntegral KeyMask
state
                        , ev_button :: EventType
ev_button        = EventType
button
                        , ev_same_screen :: Bool
ev_same_screen   = Bool
same_screen
                        }

          ---------------
          -- MotionEvent:
          ---------------
          | EventType
type_ EventType -> EventType -> Bool
forall a. Eq a => a -> a -> Bool
== EventType
motionNotify -> do
            Window
window <- (\XEventPtr
hsc_ptr -> XEventPtr -> Int -> IO Window
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff XEventPtr
hsc_ptr Int
32) XEventPtr
p
{-# LINE 539 "Graphics/X11/Xlib/Extras.hsc" #-}
            CInt
x      <- (\XEventPtr
hsc_ptr -> XEventPtr -> Int -> IO CInt
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff XEventPtr
hsc_ptr Int
64) XEventPtr
p
{-# LINE 540 "Graphics/X11/Xlib/Extras.hsc" #-}
            CInt
y      <- (\XEventPtr
hsc_ptr -> XEventPtr -> Int -> IO CInt
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff XEventPtr
hsc_ptr Int
68) XEventPtr
p
{-# LINE 541 "Graphics/X11/Xlib/Extras.hsc" #-}
            Event -> IO Event
forall (m :: * -> *) a. Monad m => a -> m a
return (Event -> IO Event) -> Event -> IO Event
forall a b. (a -> b) -> a -> b
$ MotionEvent :: EventType
-> CULong -> Bool -> Display -> CInt -> CInt -> Window -> Event
MotionEvent
                        { ev_event_type :: EventType
ev_event_type    = EventType
type_
                        , ev_serial :: CULong
ev_serial        = CULong
serial
                        , ev_send_event :: Bool
ev_send_event    = Bool
send_event
                        , ev_event_display :: Display
ev_event_display = Display
display
                        , ev_x :: CInt
ev_x             = CInt
x
                        , ev_y :: CInt
ev_y             = CInt
y
                        , ev_window :: Window
ev_window        = Window
window
                        }


          ----------------------
          -- DestroyWindowEvent:
          ----------------------
          | EventType
type_ EventType -> EventType -> Bool
forall a. Eq a => a -> a -> Bool
== EventType
destroyNotify -> do
            Window
event  <- (\XEventPtr
hsc_ptr -> XEventPtr -> Int -> IO Window
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff XEventPtr
hsc_ptr Int
32) XEventPtr
p
{-# LINE 557 "Graphics/X11/Xlib/Extras.hsc" #-}
            Window
window <- (\XEventPtr
hsc_ptr -> XEventPtr -> Int -> IO Window
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff XEventPtr
hsc_ptr Int
40) XEventPtr
p
{-# LINE 558 "Graphics/X11/Xlib/Extras.hsc" #-}
            Event -> IO Event
forall (m :: * -> *) a. Monad m => a -> m a
return (Event -> IO Event) -> Event -> IO Event
forall a b. (a -> b) -> a -> b
$ DestroyWindowEvent :: EventType -> CULong -> Bool -> Display -> Window -> Window -> Event
DestroyWindowEvent
                        { ev_event_type :: EventType
ev_event_type    = EventType
type_
                        , ev_serial :: CULong
ev_serial        = CULong
serial
                        , ev_send_event :: Bool
ev_send_event    = Bool
send_event
                        , ev_event_display :: Display
ev_event_display = Display
display
                        , ev_event :: Window
ev_event         = Window
event
                        , ev_window :: Window
ev_window        = Window
window
                        }


          --------------------
          -- UnmapNotifyEvent:
          --------------------
          | EventType
type_ EventType -> EventType -> Bool
forall a. Eq a => a -> a -> Bool
== EventType
unmapNotify -> do
            Window
event          <- (\XEventPtr
hsc_ptr -> XEventPtr -> Int -> IO Window
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff XEventPtr
hsc_ptr Int
32) XEventPtr
p
{-# LINE 573 "Graphics/X11/Xlib/Extras.hsc" #-}
            Window
window         <- (\XEventPtr
hsc_ptr -> XEventPtr -> Int -> IO Window
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff XEventPtr
hsc_ptr Int
40) XEventPtr
p
{-# LINE 574 "Graphics/X11/Xlib/Extras.hsc" #-}
            Bool
from_configure <- (\XEventPtr
hsc_ptr -> XEventPtr -> Int -> IO Bool
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff XEventPtr
hsc_ptr Int
48) XEventPtr
p
{-# LINE 575 "Graphics/X11/Xlib/Extras.hsc" #-}
            Event -> IO Event
forall (m :: * -> *) a. Monad m => a -> m a
return (Event -> IO Event) -> Event -> IO Event
forall a b. (a -> b) -> a -> b
$ UnmapEvent :: EventType
-> CULong -> Bool -> Display -> Window -> Window -> Bool -> Event
UnmapEvent
                        { ev_event_type :: EventType
ev_event_type    = EventType
type_
                        , ev_serial :: CULong
ev_serial        = CULong
serial
                        , ev_send_event :: Bool
ev_send_event    = Bool
send_event
                        , ev_event_display :: Display
ev_event_display = Display
display
                        , ev_event :: Window
ev_event         = Window
event
                        , ev_window :: Window
ev_window        = Window
window
                        , ev_from_configure :: Bool
ev_from_configure = Bool
from_configure
                        }

          --------------------
          -- CrossingEvent
          --------------------
          | EventType
type_ EventType -> EventType -> Bool
forall a. Eq a => a -> a -> Bool
== EventType
enterNotify Bool -> Bool -> Bool
|| EventType
type_ EventType -> EventType -> Bool
forall a. Eq a => a -> a -> Bool
== EventType
leaveNotify -> do
            Window
window        <- (\XEventPtr
hsc_ptr -> XEventPtr -> Int -> IO Window
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff XEventPtr
hsc_ptr Int
32) XEventPtr
p
{-# LINE 590 "Graphics/X11/Xlib/Extras.hsc" #-}
            Window
root          <- (\XEventPtr
hsc_ptr -> XEventPtr -> Int -> IO Window
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff XEventPtr
hsc_ptr Int
40) XEventPtr
p
{-# LINE 591 "Graphics/X11/Xlib/Extras.hsc" #-}
            Window
subwindow     <- (\XEventPtr
hsc_ptr -> XEventPtr -> Int -> IO Window
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff XEventPtr
hsc_ptr Int
48) XEventPtr
p
{-# LINE 592 "Graphics/X11/Xlib/Extras.hsc" #-}
            Window
time          <- (\XEventPtr
hsc_ptr -> XEventPtr -> Int -> IO Window
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff XEventPtr
hsc_ptr Int
56) XEventPtr
p
{-# LINE 593 "Graphics/X11/Xlib/Extras.hsc" #-}
            CInt
x             <- (\XEventPtr
hsc_ptr -> XEventPtr -> Int -> IO CInt
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff XEventPtr
hsc_ptr Int
64) XEventPtr
p
{-# LINE 594 "Graphics/X11/Xlib/Extras.hsc" #-}
            CInt
y             <- (\XEventPtr
hsc_ptr -> XEventPtr -> Int -> IO CInt
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff XEventPtr
hsc_ptr Int
68) XEventPtr
p
{-# LINE 595 "Graphics/X11/Xlib/Extras.hsc" #-}
            CInt
x_root        <- (\XEventPtr
hsc_ptr -> XEventPtr -> Int -> IO CInt
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff XEventPtr
hsc_ptr Int
72) XEventPtr
p
{-# LINE 596 "Graphics/X11/Xlib/Extras.hsc" #-}
            CInt
y_root        <- (\XEventPtr
hsc_ptr -> XEventPtr -> Int -> IO CInt
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff XEventPtr
hsc_ptr Int
76) XEventPtr
p
{-# LINE 597 "Graphics/X11/Xlib/Extras.hsc" #-}
            CInt
mode          <- (\XEventPtr
hsc_ptr -> XEventPtr -> Int -> IO CInt
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff XEventPtr
hsc_ptr Int
80) XEventPtr
p
{-# LINE 598 "Graphics/X11/Xlib/Extras.hsc" #-}
            CInt
detail        <- (\XEventPtr
hsc_ptr -> XEventPtr -> Int -> IO CInt
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff XEventPtr
hsc_ptr Int
84) XEventPtr
p
{-# LINE 599 "Graphics/X11/Xlib/Extras.hsc" #-}
            Bool
same_screen   <- (\XEventPtr
hsc_ptr -> XEventPtr -> Int -> IO Bool
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff XEventPtr
hsc_ptr Int
88) XEventPtr
p
{-# LINE 600 "Graphics/X11/Xlib/Extras.hsc" #-}
            Bool
focus         <- (\XEventPtr
hsc_ptr -> XEventPtr -> Int -> IO Bool
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff XEventPtr
hsc_ptr Int
92) XEventPtr
p
{-# LINE 601 "Graphics/X11/Xlib/Extras.hsc" #-}
            KeyMask
state         <- ((\XEventPtr
hsc_ptr -> XEventPtr -> Int -> IO KeyMask
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff XEventPtr
hsc_ptr Int
96) XEventPtr
p) :: IO CUInt
{-# LINE 602 "Graphics/X11/Xlib/Extras.hsc" #-}

            Event -> IO Event
forall (m :: * -> *) a. Monad m => a -> m a
return (Event -> IO Event) -> Event -> IO Event
forall a b. (a -> b) -> a -> b
$ CrossingEvent :: EventType
-> CULong
-> Bool
-> Display
-> Window
-> Window
-> Window
-> Window
-> CInt
-> CInt
-> CInt
-> CInt
-> CInt
-> CInt
-> Bool
-> Bool
-> KeyMask
-> Event
CrossingEvent
                        { ev_event_type :: EventType
ev_event_type    = EventType
type_
                        , ev_serial :: CULong
ev_serial        = CULong
serial
                        , ev_send_event :: Bool
ev_send_event    = Bool
send_event
                        , ev_event_display :: Display
ev_event_display = Display
display
                        , ev_window :: Window
ev_window        = Window
window
                        , ev_root :: Window
ev_root          = Window
root
                        , ev_subwindow :: Window
ev_subwindow     = Window
subwindow
                        , ev_time :: Window
ev_time          = Window
time
                        , ev_x :: CInt
ev_x             = CInt
x
                        , ev_y :: CInt
ev_y             = CInt
y
                        , ev_x_root :: CInt
ev_x_root        = CInt
x_root
                        , ev_y_root :: CInt
ev_y_root        = CInt
y_root
                        , ev_mode :: CInt
ev_mode          = CInt
mode
                        , ev_detail :: CInt
ev_detail        = CInt
detail
                        , ev_same_screen :: Bool
ev_same_screen   = Bool
same_screen
                        , ev_focus :: Bool
ev_focus         = Bool
focus
                        , ev_state :: KeyMask
ev_state         = KeyMask -> KeyMask
forall a b. (Integral a, Num b) => a -> b
fromIntegral KeyMask
state
                        }

          -------------------------
          -- SelectionRequestEvent:
          -------------------------
          | EventType
type_ EventType -> EventType -> Bool
forall a. Eq a => a -> a -> Bool
== EventType
selectionRequest -> do
            Window
owner          <- (\XEventPtr
hsc_ptr -> XEventPtr -> Int -> IO Window
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff XEventPtr
hsc_ptr Int
32) XEventPtr
p
{-# LINE 628 "Graphics/X11/Xlib/Extras.hsc" #-}
            Window
requestor      <- (\XEventPtr
hsc_ptr -> XEventPtr -> Int -> IO Window
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff XEventPtr
hsc_ptr Int
40) XEventPtr
p
{-# LINE 629 "Graphics/X11/Xlib/Extras.hsc" #-}
            Window
selection      <- (\XEventPtr
hsc_ptr -> XEventPtr -> Int -> IO Window
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff XEventPtr
hsc_ptr Int
48) XEventPtr
p
{-# LINE 630 "Graphics/X11/Xlib/Extras.hsc" #-}
            Window
target         <- (\XEventPtr
hsc_ptr -> XEventPtr -> Int -> IO Window
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff XEventPtr
hsc_ptr Int
56) XEventPtr
p
{-# LINE 631 "Graphics/X11/Xlib/Extras.hsc" #-}
            Window
property       <- (\XEventPtr
hsc_ptr -> XEventPtr -> Int -> IO Window
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff XEventPtr
hsc_ptr Int
64) XEventPtr
p
{-# LINE 632 "Graphics/X11/Xlib/Extras.hsc" #-}
            Window
time           <- (\XEventPtr
hsc_ptr -> XEventPtr -> Int -> IO Window
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff XEventPtr
hsc_ptr Int
72) XEventPtr
p
{-# LINE 633 "Graphics/X11/Xlib/Extras.hsc" #-}
            Event -> IO Event
forall (m :: * -> *) a. Monad m => a -> m a
return (Event -> IO Event) -> Event -> IO Event
forall a b. (a -> b) -> a -> b
$ SelectionRequest :: EventType
-> CULong
-> Bool
-> Display
-> Window
-> Window
-> Window
-> Window
-> Window
-> Window
-> Event
SelectionRequest
                        { ev_event_type :: EventType
ev_event_type    = EventType
type_
                        , ev_serial :: CULong
ev_serial        = CULong
serial
                        , ev_send_event :: Bool
ev_send_event    = Bool
send_event
                        , ev_event_display :: Display
ev_event_display = Display
display
                        , ev_owner :: Window
ev_owner         = Window
owner
                        , ev_requestor :: Window
ev_requestor     = Window
requestor
                        , ev_selection :: Window
ev_selection     = Window
selection
                        , ev_target :: Window
ev_target        = Window
target
                        , ev_property :: Window
ev_property      = Window
property
                        , ev_time :: Window
ev_time          = Window
time
                        }

          -------------------------
          -- SelectionClearEvent:
          -------------------------
          | EventType
type_ EventType -> EventType -> Bool
forall a. Eq a => a -> a -> Bool
== EventType
selectionClear -> do
            Window
window <- (\XEventPtr
hsc_ptr -> XEventPtr -> Int -> IO Window
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff XEventPtr
hsc_ptr Int
32) XEventPtr
p
{-# LINE 651 "Graphics/X11/Xlib/Extras.hsc" #-}
            Window
atom   <- (\XEventPtr
hsc_ptr -> XEventPtr -> Int -> IO Window
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff XEventPtr
hsc_ptr Int
40) XEventPtr
p
{-# LINE 652 "Graphics/X11/Xlib/Extras.hsc" #-}
            Window
time   <- (\XEventPtr
hsc_ptr -> XEventPtr -> Int -> IO Window
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff XEventPtr
hsc_ptr Int
48) XEventPtr
p
{-# LINE 653 "Graphics/X11/Xlib/Extras.hsc" #-}
            Event -> IO Event
forall (m :: * -> *) a. Monad m => a -> m a
return (Event -> IO Event) -> Event -> IO Event
forall a b. (a -> b) -> a -> b
$ SelectionClear :: EventType
-> CULong -> Bool -> Display -> Window -> Window -> Window -> Event
SelectionClear
                        { ev_event_type :: EventType
ev_event_type    = EventType
type_
                        , ev_serial :: CULong
ev_serial        = CULong
serial
                        , ev_send_event :: Bool
ev_send_event    = Bool
send_event
                        , ev_event_display :: Display
ev_event_display = Display
display
                        , ev_window :: Window
ev_window        = Window
window
                        , ev_selection :: Window
ev_selection     = Window
atom
                        , ev_time :: Window
ev_time          = Window
time
                        }
          -------------------------
          -- PropertyEvent
          -------------------------
          | EventType
type_ EventType -> EventType -> Bool
forall a. Eq a => a -> a -> Bool
== EventType
propertyNotify -> do
            Window
window <- (\XEventPtr
hsc_ptr -> XEventPtr -> Int -> IO Window
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff XEventPtr
hsc_ptr Int
32) XEventPtr
p
{-# LINE 667 "Graphics/X11/Xlib/Extras.hsc" #-}
            Window
atom   <- (\XEventPtr
hsc_ptr -> XEventPtr -> Int -> IO Window
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff XEventPtr
hsc_ptr Int
40) XEventPtr
p
{-# LINE 668 "Graphics/X11/Xlib/Extras.hsc" #-}
            Window
time   <- (\XEventPtr
hsc_ptr -> XEventPtr -> Int -> IO Window
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff XEventPtr
hsc_ptr Int
48) XEventPtr
p
{-# LINE 669 "Graphics/X11/Xlib/Extras.hsc" #-}
            CInt
state  <- (\XEventPtr
hsc_ptr -> XEventPtr -> Int -> IO CInt
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff XEventPtr
hsc_ptr Int
56) XEventPtr
p
{-# LINE 670 "Graphics/X11/Xlib/Extras.hsc" #-}
            Event -> IO Event
forall (m :: * -> *) a. Monad m => a -> m a
return (Event -> IO Event) -> Event -> IO Event
forall a b. (a -> b) -> a -> b
$ PropertyEvent :: EventType
-> CULong
-> Bool
-> Display
-> Window
-> Window
-> Window
-> CInt
-> Event
PropertyEvent
                        { ev_event_type :: EventType
ev_event_type    = EventType
type_
                        , ev_serial :: CULong
ev_serial        = CULong
serial
                        , ev_send_event :: Bool
ev_send_event    = Bool
send_event
                        , ev_event_display :: Display
ev_event_display = Display
display
                        , ev_window :: Window
ev_window        = Window
window
                        , ev_atom :: Window
ev_atom          = Window
atom
                        , ev_time :: Window
ev_time          = Window
time
                        , ev_propstate :: CInt
ev_propstate     = CInt
state
                        }

          -------------------------
          -- ExposeEvent
          -------------------------
          | EventType
type_ EventType -> EventType -> Bool
forall a. Eq a => a -> a -> Bool
== EventType
expose -> do
            Window
window <- (\XEventPtr
hsc_ptr -> XEventPtr -> Int -> IO Window
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff XEventPtr
hsc_ptr Int
32) XEventPtr
p
{-# LINE 686 "Graphics/X11/Xlib/Extras.hsc" #-}
            CInt
x      <- (\XEventPtr
hsc_ptr -> XEventPtr -> Int -> IO CInt
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff XEventPtr
hsc_ptr Int
40) XEventPtr
p
{-# LINE 687 "Graphics/X11/Xlib/Extras.hsc" #-}
            CInt
y      <- (\XEventPtr
hsc_ptr -> XEventPtr -> Int -> IO CInt
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff XEventPtr
hsc_ptr Int
44) XEventPtr
p
{-# LINE 688 "Graphics/X11/Xlib/Extras.hsc" #-}
            CInt
width  <- (\XEventPtr
hsc_ptr -> XEventPtr -> Int -> IO CInt
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff XEventPtr
hsc_ptr Int
48) XEventPtr
p
{-# LINE 689 "Graphics/X11/Xlib/Extras.hsc" #-}
            CInt
height <- (\XEventPtr
hsc_ptr -> XEventPtr -> Int -> IO CInt
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff XEventPtr
hsc_ptr Int
52) XEventPtr
p
{-# LINE 690 "Graphics/X11/Xlib/Extras.hsc" #-}
            CInt
count  <- (\XEventPtr
hsc_ptr -> XEventPtr -> Int -> IO CInt
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff XEventPtr
hsc_ptr Int
56) XEventPtr
p
{-# LINE 691 "Graphics/X11/Xlib/Extras.hsc" #-}
            Event -> IO Event
forall (m :: * -> *) a. Monad m => a -> m a
return (Event -> IO Event) -> Event -> IO Event
forall a b. (a -> b) -> a -> b
$ ExposeEvent :: EventType
-> CULong
-> Bool
-> Display
-> Window
-> CInt
-> CInt
-> CInt
-> CInt
-> CInt
-> Event
ExposeEvent
                        { ev_event_type :: EventType
ev_event_type    = EventType
type_
                        , ev_serial :: CULong
ev_serial        = CULong
serial
                        , ev_send_event :: Bool
ev_send_event    = Bool
send_event
                        , ev_event_display :: Display
ev_event_display = Display
display
                        , ev_window :: Window
ev_window        = Window
window
                        , ev_x :: CInt
ev_x             = CInt
x
                        , ev_y :: CInt
ev_y             = CInt
y
                        , ev_width :: CInt
ev_width         = CInt
width
                        , ev_height :: CInt
ev_height        = CInt
height
                        , ev_count :: CInt
ev_count         = CInt
count
                        }

          -------------------------
          -- ClientMessageEvent
          -------------------------
          | EventType
type_ EventType -> EventType -> Bool
forall a. Eq a => a -> a -> Bool
== EventType
clientMessage -> do
            Window
window       <- (\XEventPtr
hsc_ptr -> XEventPtr -> Int -> IO Window
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff XEventPtr
hsc_ptr Int
32) XEventPtr
p
{-# LINE 709 "Graphics/X11/Xlib/Extras.hsc" #-}
            Window
message_type <- (\XEventPtr
hsc_ptr -> XEventPtr -> Int -> IO Window
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff XEventPtr
hsc_ptr Int
40) XEventPtr
p
{-# LINE 710 "Graphics/X11/Xlib/Extras.hsc" #-}
            CInt
format       <- (\XEventPtr
hsc_ptr -> XEventPtr -> Int -> IO CInt
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff XEventPtr
hsc_ptr Int
48) XEventPtr
p
{-# LINE 711 "Graphics/X11/Xlib/Extras.hsc" #-}
            let datPtr :: Ptr b
datPtr =    (\XEventPtr
hsc_ptr -> XEventPtr
hsc_ptr XEventPtr -> Int -> Ptr b
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
56) XEventPtr
p
{-# LINE 712 "Graphics/X11/Xlib/Extras.hsc" #-}
            [CInt]
dat          <- case (CInt
format::CInt) of
                        CInt
8  -> do [KeyCode]
a <- Int -> Ptr KeyCode -> IO [KeyCode]
forall a. Storable a => Int -> Ptr a -> IO [a]
peekArray Int
20 Ptr KeyCode
forall b. Ptr b
datPtr
                                 [CInt] -> IO [CInt]
forall (m :: * -> *) a. Monad m => a -> m a
return ([CInt] -> IO [CInt]) -> [CInt] -> IO [CInt]
forall a b. (a -> b) -> a -> b
$ (KeyCode -> CInt) -> [KeyCode] -> [CInt]
forall a b. (a -> b) -> [a] -> [b]
map KeyCode -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral ([KeyCode]
a::[Word8])
                        CInt
16 -> do [SizeID]
a <- Int -> Ptr SizeID -> IO [SizeID]
forall a. Storable a => Int -> Ptr a -> IO [a]
peekArray Int
10 Ptr SizeID
forall b. Ptr b
datPtr
                                 [CInt] -> IO [CInt]
forall (m :: * -> *) a. Monad m => a -> m a
return ([CInt] -> IO [CInt]) -> [CInt] -> IO [CInt]
forall a b. (a -> b) -> a -> b
$ (SizeID -> CInt) -> [SizeID] -> [CInt]
forall a b. (a -> b) -> [a] -> [b]
map SizeID -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral ([SizeID]
a::[Word16])
                        CInt
32 -> do [CLong]
a <- Int -> Ptr CLong -> IO [CLong]
forall a. Storable a => Int -> Ptr a -> IO [a]
peekArray Int
5 Ptr CLong
forall b. Ptr b
datPtr
                                 [CInt] -> IO [CInt]
forall (m :: * -> *) a. Monad m => a -> m a
return ([CInt] -> IO [CInt]) -> [CInt] -> IO [CInt]
forall a b. (a -> b) -> a -> b
$ (CLong -> CInt) -> [CLong] -> [CInt]
forall a b. (a -> b) -> [a] -> [b]
map CLong -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral ([CLong]
a::[CLong])
                        CInt
_  -> String -> IO [CInt]
forall a. HasCallStack => String -> a
error String
"X11.Extras.clientMessage: illegal value"
            Event -> IO Event
forall (m :: * -> *) a. Monad m => a -> m a
return (Event -> IO Event) -> Event -> IO Event
forall a b. (a -> b) -> a -> b
$ ClientMessageEvent :: EventType
-> CULong -> Bool -> Display -> Window -> Window -> [CInt] -> Event
ClientMessageEvent
                        { ev_event_type :: EventType
ev_event_type    = EventType
type_
                        , ev_serial :: CULong
ev_serial        = CULong
serial
                        , ev_send_event :: Bool
ev_send_event    = Bool
send_event
                        , ev_event_display :: Display
ev_event_display = Display
display
                        , ev_window :: Window
ev_window        = Window
window
                        , ev_message_type :: Window
ev_message_type  = Window
message_type
                        , ev_data :: [CInt]
ev_data          = [CInt]
dat
                        }

          -------------------------
          -- RRScreenChangeNotify
          -------------------------
          | Bool
rrHasExtension Bool -> Bool -> Bool
&&
            EventType
type_ EventType -> EventType -> Bool
forall a. Eq a => a -> a -> Bool
== EventType
rrEventBase EventType -> EventType -> EventType
forall a. Num a => a -> a -> a
+ EventType
rrScreenChangeNotify -> do
            Window
window           <- (\XEventPtr
hsc_ptr -> XEventPtr -> Int -> IO Window
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff XEventPtr
hsc_ptr Int
32) XEventPtr
p
{-# LINE 736 "Graphics/X11/Xlib/Extras.hsc" #-}
            Window
root             <- (\XEventPtr
hsc_ptr -> XEventPtr -> Int -> IO Window
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff XEventPtr
hsc_ptr Int
40) XEventPtr
p
{-# LINE 737 "Graphics/X11/Xlib/Extras.hsc" #-}
            Window
timestamp        <- (\XEventPtr
hsc_ptr -> XEventPtr -> Int -> IO Window
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff XEventPtr
hsc_ptr Int
48) XEventPtr
p
{-# LINE 738 "Graphics/X11/Xlib/Extras.hsc" #-}
            Window
config_timestamp <- (\XEventPtr
hsc_ptr -> XEventPtr -> Int -> IO Window
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff XEventPtr
hsc_ptr Int
56) XEventPtr
p
{-# LINE 739 "Graphics/X11/Xlib/Extras.hsc" #-}
            SizeID
size_index       <- (\XEventPtr
hsc_ptr -> XEventPtr -> Int -> IO SizeID
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff XEventPtr
hsc_ptr Int
56) XEventPtr
p
{-# LINE 740 "Graphics/X11/Xlib/Extras.hsc" #-}
            SizeID
subpixel_order   <- (\XEventPtr
hsc_ptr -> XEventPtr -> Int -> IO SizeID
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff XEventPtr
hsc_ptr Int
66) XEventPtr
p
{-# LINE 741 "Graphics/X11/Xlib/Extras.hsc" #-}
            SizeID
rotation         <- (\XEventPtr
hsc_ptr -> XEventPtr -> Int -> IO SizeID
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff XEventPtr
hsc_ptr Int
68) XEventPtr
p
{-# LINE 742 "Graphics/X11/Xlib/Extras.hsc" #-}
            CInt
width            <- (\XEventPtr
hsc_ptr -> XEventPtr -> Int -> IO CInt
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff XEventPtr
hsc_ptr Int
72) XEventPtr
p
{-# LINE 743 "Graphics/X11/Xlib/Extras.hsc" #-}
            CInt
height           <- (\XEventPtr
hsc_ptr -> XEventPtr -> Int -> IO CInt
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff XEventPtr
hsc_ptr Int
76) XEventPtr
p
{-# LINE 744 "Graphics/X11/Xlib/Extras.hsc" #-}
            CInt
mwidth           <- (\XEventPtr
hsc_ptr -> XEventPtr -> Int -> IO CInt
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff XEventPtr
hsc_ptr Int
80) XEventPtr
p
{-# LINE 745 "Graphics/X11/Xlib/Extras.hsc" #-}
            CInt
mheight          <- (\XEventPtr
hsc_ptr -> XEventPtr -> Int -> IO CInt
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff XEventPtr
hsc_ptr Int
84) XEventPtr
p
{-# LINE 746 "Graphics/X11/Xlib/Extras.hsc" #-}
            Event -> IO Event
forall (m :: * -> *) a. Monad m => a -> m a
return (Event -> IO Event) -> Event -> IO Event
forall a b. (a -> b) -> a -> b
$ RRScreenChangeNotifyEvent :: EventType
-> CULong
-> Bool
-> Display
-> Window
-> Window
-> Window
-> Window
-> SizeID
-> SizeID
-> SizeID
-> CInt
-> CInt
-> CInt
-> CInt
-> Event
RRScreenChangeNotifyEvent
                        { ev_event_type :: EventType
ev_event_type       = EventType
type_
                        , ev_serial :: CULong
ev_serial           = CULong
serial
                        , ev_send_event :: Bool
ev_send_event       = Bool
send_event
                        , ev_event_display :: Display
ev_event_display    = Display
display
                        , ev_window :: Window
ev_window           = Window
window
                        , ev_root :: Window
ev_root             = Window
root
                        , ev_timestamp :: Window
ev_timestamp        = Window
timestamp
                        , ev_config_timestamp :: Window
ev_config_timestamp = Window
config_timestamp
                        , ev_size_index :: SizeID
ev_size_index       = SizeID
size_index
                        , ev_subpixel_order :: SizeID
ev_subpixel_order   = SizeID
subpixel_order
                        , ev_rotation :: SizeID
ev_rotation         = SizeID
rotation
                        , ev_width :: CInt
ev_width            = CInt
width
                        , ev_height :: CInt
ev_height           = CInt
height
                        , ev_mwidth :: CInt
ev_mwidth           = CInt
mwidth
                        , ev_mheight :: CInt
ev_mheight          = CInt
mheight
                        }

          -------------------------
          -- RRNotify
          -------------------------
          | Bool
rrHasExtension Bool -> Bool -> Bool
&&
            EventType
type_ EventType -> EventType -> Bool
forall a. Eq a => a -> a -> Bool
== EventType
rrEventBase EventType -> EventType -> EventType
forall a. Num a => a -> a -> a
+ EventType
rrNotify -> do
            Window
window   <- (\XEventPtr
hsc_ptr -> XEventPtr -> Int -> IO Window
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff XEventPtr
hsc_ptr Int
32) XEventPtr
p
{-# LINE 770 "Graphics/X11/Xlib/Extras.hsc" #-}
            CInt
subtype  <- (\XEventPtr
hsc_ptr -> XEventPtr -> Int -> IO CInt
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff XEventPtr
hsc_ptr Int
40) XEventPtr
p
{-# LINE 771 "Graphics/X11/Xlib/Extras.hsc" #-}
            let subtype_ :: EventType
subtype_ = CInt -> EventType
forall a b. (Integral a, Num b) => a -> b
fromIntegral CInt
subtype
            case () of
                ()
_ | EventType
subtype_ EventType -> EventType -> Bool
forall a. Eq a => a -> a -> Bool
== EventType
rrNotifyCrtcChange -> do
                    Window
crtc           <- (\XEventPtr
hsc_ptr -> XEventPtr -> Int -> IO Window
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff XEventPtr
hsc_ptr Int
48) XEventPtr
p
{-# LINE 775 "Graphics/X11/Xlib/Extras.hsc" #-}
                    Window
mode           <- (\XEventPtr
hsc_ptr -> XEventPtr -> Int -> IO Window
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff XEventPtr
hsc_ptr Int
56) XEventPtr
p
{-# LINE 776 "Graphics/X11/Xlib/Extras.hsc" #-}
                    SizeID
rotation       <- (\XEventPtr
hsc_ptr -> XEventPtr -> Int -> IO SizeID
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff XEventPtr
hsc_ptr Int
64) XEventPtr
p
{-# LINE 777 "Graphics/X11/Xlib/Extras.hsc" #-}
                    CInt
x              <- (\XEventPtr
hsc_ptr -> XEventPtr -> Int -> IO CInt
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff XEventPtr
hsc_ptr Int
68) XEventPtr
p
{-# LINE 778 "Graphics/X11/Xlib/Extras.hsc" #-}
                    CInt
y              <- (\XEventPtr
hsc_ptr -> XEventPtr -> Int -> IO CInt
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff XEventPtr
hsc_ptr Int
72) XEventPtr
p
{-# LINE 779 "Graphics/X11/Xlib/Extras.hsc" #-}
                    KeyMask
width          <- (\XEventPtr
hsc_ptr -> XEventPtr -> Int -> IO KeyMask
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff XEventPtr
hsc_ptr Int
76) XEventPtr
p
{-# LINE 780 "Graphics/X11/Xlib/Extras.hsc" #-}
                    KeyMask
height         <- (\XEventPtr
hsc_ptr -> XEventPtr -> Int -> IO KeyMask
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff XEventPtr
hsc_ptr Int
80) XEventPtr
p
{-# LINE 781 "Graphics/X11/Xlib/Extras.hsc" #-}
                    Event -> IO Event
forall (m :: * -> *) a. Monad m => a -> m a
return (Event -> IO Event) -> Event -> IO Event
forall a b. (a -> b) -> a -> b
$ RRCrtcChangeNotifyEvent :: EventType
-> CULong
-> Bool
-> Display
-> Window
-> CInt
-> Window
-> Window
-> SizeID
-> CInt
-> CInt
-> KeyMask
-> KeyMask
-> Event
RRCrtcChangeNotifyEvent
                             { ev_event_type :: EventType
ev_event_type    = EventType
type_
                             , ev_serial :: CULong
ev_serial        = CULong
serial
                             , ev_send_event :: Bool
ev_send_event    = Bool
send_event
                             , ev_event_display :: Display
ev_event_display = Display
display
                             , ev_window :: Window
ev_window        = Window
window
                             , ev_subtype :: CInt
ev_subtype       = CInt
subtype
                             , ev_crtc :: Window
ev_crtc          = Window
crtc
                             , ev_rr_mode :: Window
ev_rr_mode       = Window
mode
                             , ev_rotation :: SizeID
ev_rotation      = SizeID
rotation
                             , ev_x :: CInt
ev_x             = CInt
x
                             , ev_y :: CInt
ev_y             = CInt
y
                             , ev_rr_width :: KeyMask
ev_rr_width      = KeyMask
width
                             , ev_rr_height :: KeyMask
ev_rr_height     = KeyMask
height
                             }

                  | EventType
subtype_ EventType -> EventType -> Bool
forall a. Eq a => a -> a -> Bool
== EventType
rrNotifyOutputChange -> do
                    Window
output         <- (\XEventPtr
hsc_ptr -> XEventPtr -> Int -> IO Window
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff XEventPtr
hsc_ptr Int
48) XEventPtr
p
{-# LINE 799 "Graphics/X11/Xlib/Extras.hsc" #-}
                    Window
crtc           <- (\XEventPtr
hsc_ptr -> XEventPtr -> Int -> IO Window
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff XEventPtr
hsc_ptr Int
56) XEventPtr
p
{-# LINE 800 "Graphics/X11/Xlib/Extras.hsc" #-}
                    Window
mode           <- (\XEventPtr
hsc_ptr -> XEventPtr -> Int -> IO Window
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff XEventPtr
hsc_ptr Int
64) XEventPtr
p
{-# LINE 801 "Graphics/X11/Xlib/Extras.hsc" #-}
                    SizeID
rotation       <- (\XEventPtr
hsc_ptr -> XEventPtr -> Int -> IO SizeID
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff XEventPtr
hsc_ptr Int
72) XEventPtr
p
{-# LINE 802 "Graphics/X11/Xlib/Extras.hsc" #-}
                    SizeID
connection     <- (\XEventPtr
hsc_ptr -> XEventPtr -> Int -> IO SizeID
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff XEventPtr
hsc_ptr Int
74) XEventPtr
p
{-# LINE 803 "Graphics/X11/Xlib/Extras.hsc" #-}
                    SizeID
subpixel_order <- (\XEventPtr
hsc_ptr -> XEventPtr -> Int -> IO SizeID
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff XEventPtr
hsc_ptr Int
76) XEventPtr
p
{-# LINE 804 "Graphics/X11/Xlib/Extras.hsc" #-}
                    Event -> IO Event
forall (m :: * -> *) a. Monad m => a -> m a
return (Event -> IO Event) -> Event -> IO Event
forall a b. (a -> b) -> a -> b
$ RROutputChangeNotifyEvent :: EventType
-> CULong
-> Bool
-> Display
-> Window
-> CInt
-> Window
-> Window
-> Window
-> SizeID
-> SizeID
-> SizeID
-> Event
RROutputChangeNotifyEvent
                             { ev_event_type :: EventType
ev_event_type     = EventType
type_
                             , ev_serial :: CULong
ev_serial         = CULong
serial
                             , ev_send_event :: Bool
ev_send_event     = Bool
send_event
                             , ev_event_display :: Display
ev_event_display  = Display
display
                             , ev_window :: Window
ev_window         = Window
window
                             , ev_subtype :: CInt
ev_subtype        = CInt
subtype
                             , ev_output :: Window
ev_output         = Window
output
                             , ev_crtc :: Window
ev_crtc           = Window
crtc
                             , ev_rr_mode :: Window
ev_rr_mode        = Window
mode
                             , ev_rotation :: SizeID
ev_rotation       = SizeID
rotation
                             , ev_connection :: SizeID
ev_connection     = SizeID
connection
                             , ev_subpixel_order :: SizeID
ev_subpixel_order = SizeID
subpixel_order
                             }

                  | EventType
subtype_ EventType -> EventType -> Bool
forall a. Eq a => a -> a -> Bool
== EventType
rrNotifyOutputProperty -> do
                    Window
output         <- (\XEventPtr
hsc_ptr -> XEventPtr -> Int -> IO Window
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff XEventPtr
hsc_ptr Int
48) XEventPtr
p
{-# LINE 821 "Graphics/X11/Xlib/Extras.hsc" #-}
                    Window
property       <- (\XEventPtr
hsc_ptr -> XEventPtr -> Int -> IO Window
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff XEventPtr
hsc_ptr Int
56) XEventPtr
p
{-# LINE 822 "Graphics/X11/Xlib/Extras.hsc" #-}
                    Window
timestamp      <- (\XEventPtr
hsc_ptr -> XEventPtr -> Int -> IO Window
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff XEventPtr
hsc_ptr Int
64) XEventPtr
p
{-# LINE 823 "Graphics/X11/Xlib/Extras.hsc" #-}
                    CInt
state          <- (\XEventPtr
hsc_ptr -> XEventPtr -> Int -> IO CInt
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff XEventPtr
hsc_ptr Int
72) XEventPtr
p
{-# LINE 824 "Graphics/X11/Xlib/Extras.hsc" #-}
                    Event -> IO Event
forall (m :: * -> *) a. Monad m => a -> m a
return (Event -> IO Event) -> Event -> IO Event
forall a b. (a -> b) -> a -> b
$ RROutputPropertyNotifyEvent :: EventType
-> CULong
-> Bool
-> Display
-> Window
-> CInt
-> Window
-> Window
-> Window
-> CInt
-> Event
RROutputPropertyNotifyEvent
                             { ev_event_type :: EventType
ev_event_type    = EventType
type_
                             , ev_serial :: CULong
ev_serial        = CULong
serial
                             , ev_send_event :: Bool
ev_send_event    = Bool
send_event
                             , ev_event_display :: Display
ev_event_display = Display
display
                             , ev_window :: Window
ev_window        = Window
window
                             , ev_subtype :: CInt
ev_subtype       = CInt
subtype
                             , ev_output :: Window
ev_output        = Window
output
                             , ev_property :: Window
ev_property      = Window
property
                             , ev_timestamp :: Window
ev_timestamp     = Window
timestamp
                             , ev_rr_state :: CInt
ev_rr_state      = CInt
state
                             }

                  -- We don't handle this event specifically, so return the generic
                  -- RRNotifyEvent.
                  | Bool
otherwise -> do
                    Event -> IO Event
forall (m :: * -> *) a. Monad m => a -> m a
return (Event -> IO Event) -> Event -> IO Event
forall a b. (a -> b) -> a -> b
$ RRNotifyEvent :: EventType -> CULong -> Bool -> Display -> Window -> CInt -> Event
RRNotifyEvent
                                { ev_event_type :: EventType
ev_event_type    = EventType
type_
                                , ev_serial :: CULong
ev_serial        = CULong
serial
                                , ev_send_event :: Bool
ev_send_event    = Bool
send_event
                                , ev_event_display :: Display
ev_event_display = Display
display
                                , ev_window :: Window
ev_window        = Window
window
                                , ev_subtype :: CInt
ev_subtype       = CInt
subtype
                                }

          -----------------
          -- ScreenSaverNotifyEvent:
          -----------------
          | EventType
type_ EventType -> EventType -> Bool
forall a. Eq a => a -> a -> Bool
== EventType
screenSaverNotify -> do
            (Window
 -> Window
 -> XScreenSaverState
 -> XScreenSaverKind
 -> Bool
 -> Window
 -> Event)
-> IO
     (Window
      -> Window
      -> XScreenSaverState
      -> XScreenSaverKind
      -> Bool
      -> Window
      -> Event)
forall (m :: * -> *) a. Monad m => a -> m a
return (EventType
-> CULong
-> Bool
-> Display
-> Window
-> Window
-> XScreenSaverState
-> XScreenSaverKind
-> Bool
-> Window
-> Event
ScreenSaverNotifyEvent EventType
type_ CULong
serial Bool
send_event Display
display)
                IO
  (Window
   -> Window
   -> XScreenSaverState
   -> XScreenSaverKind
   -> Bool
   -> Window
   -> Event)
-> IO Window
-> IO
     (Window
      -> XScreenSaverState
      -> XScreenSaverKind
      -> Bool
      -> Window
      -> Event)
forall (m :: * -> *) a b. Monad m => m (a -> b) -> m a -> m b
`ap` ((\XEventPtr
hsc_ptr -> XEventPtr -> Int -> IO Window
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff XEventPtr
hsc_ptr Int
32) XEventPtr
p )
{-# LINE 855 "Graphics/X11/Xlib/Extras.hsc" #-}
                IO
  (Window
   -> XScreenSaverState
   -> XScreenSaverKind
   -> Bool
   -> Window
   -> Event)
-> IO Window
-> IO
     (XScreenSaverState -> XScreenSaverKind -> Bool -> Window -> Event)
forall (m :: * -> *) a b. Monad m => m (a -> b) -> m a -> m b
`ap` ((\XEventPtr
hsc_ptr -> XEventPtr -> Int -> IO Window
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff XEventPtr
hsc_ptr Int
40) XEventPtr
p )
{-# LINE 856 "Graphics/X11/Xlib/Extras.hsc" #-}
                IO
  (XScreenSaverState -> XScreenSaverKind -> Bool -> Window -> Event)
-> IO XScreenSaverState
-> IO (XScreenSaverKind -> Bool -> Window -> Event)
forall (m :: * -> *) a b. Monad m => m (a -> b) -> m a -> m b
`ap` ((\XEventPtr
hsc_ptr -> XEventPtr -> Int -> IO XScreenSaverState
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff XEventPtr
hsc_ptr Int
48) XEventPtr
p )
{-# LINE 857 "Graphics/X11/Xlib/Extras.hsc" #-}
                IO (XScreenSaverKind -> Bool -> Window -> Event)
-> IO XScreenSaverKind -> IO (Bool -> Window -> Event)
forall (m :: * -> *) a b. Monad m => m (a -> b) -> m a -> m b
`ap` ((\XEventPtr
hsc_ptr -> XEventPtr -> Int -> IO XScreenSaverKind
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff XEventPtr
hsc_ptr Int
52) XEventPtr
p )
{-# LINE 858 "Graphics/X11/Xlib/Extras.hsc" #-}
                IO (Bool -> Window -> Event) -> IO Bool -> IO (Window -> Event)
forall (m :: * -> *) a b. Monad m => m (a -> b) -> m a -> m b
`ap` ((\XEventPtr
hsc_ptr -> XEventPtr -> Int -> IO Bool
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff XEventPtr
hsc_ptr Int
56) XEventPtr
p )
{-# LINE 859 "Graphics/X11/Xlib/Extras.hsc" #-}
                IO (Window -> Event) -> IO Window -> IO Event
forall (m :: * -> *) a b. Monad m => m (a -> b) -> m a -> m b
`ap` ((\XEventPtr
hsc_ptr -> XEventPtr -> Int -> IO Window
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff XEventPtr
hsc_ptr Int
64) XEventPtr
p )
{-# LINE 860 "Graphics/X11/Xlib/Extras.hsc" #-}

          -- We don't handle this event specifically, so return the generic
          -- AnyEvent.
          | Bool
otherwise -> do
            Window
window <- (\XEventPtr
hsc_ptr -> XEventPtr -> Int -> IO Window
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff XEventPtr
hsc_ptr Int
32) XEventPtr
p
{-# LINE 865 "Graphics/X11/Xlib/Extras.hsc" #-}
            Event -> IO Event
forall (m :: * -> *) a. Monad m => a -> m a
return (Event -> IO Event) -> Event -> IO Event
forall a b. (a -> b) -> a -> b
$ AnyEvent :: EventType -> CULong -> Bool -> Display -> Window -> Event
AnyEvent
                        { ev_event_type :: EventType
ev_event_type    = EventType
type_
                        , ev_serial :: CULong
ev_serial        = CULong
serial
                        , ev_send_event :: Bool
ev_send_event    = Bool
send_event
                        , ev_event_display :: Display
ev_event_display = Display
display
                        , ev_window :: Window
ev_window        = Window
window
                        }

data WindowChanges = WindowChanges
                        { WindowChanges -> CInt
wc_x :: CInt
                        , WindowChanges -> CInt
wc_y :: CInt
                        , WindowChanges -> CInt
wc_width :: CInt
                        , WindowChanges -> CInt
wc_height:: CInt
                        , WindowChanges -> CInt
wc_border_width :: CInt
                        , WindowChanges -> Window
wc_sibling :: Window
                        , WindowChanges -> CInt
wc_stack_mode :: CInt
                        }

instance Storable WindowChanges where
    sizeOf :: WindowChanges -> Int
sizeOf WindowChanges
_ = (Int
40)
{-# LINE 885 "Graphics/X11/Xlib/Extras.hsc" #-}

    -- I really hope this is right:
    alignment :: WindowChanges -> Int
alignment WindowChanges
_ = CInt -> Int
forall a. Storable a => a -> Int
alignment (CInt
forall a. HasCallStack => a
undefined :: CInt)

    poke :: Ptr WindowChanges -> WindowChanges -> IO ()
poke Ptr WindowChanges
p WindowChanges
wc = do
        (\Ptr WindowChanges
hsc_ptr -> Ptr WindowChanges -> Int -> CInt -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr WindowChanges
hsc_ptr Int
0) Ptr WindowChanges
p (CInt -> IO ()) -> CInt -> IO ()
forall a b. (a -> b) -> a -> b
$ WindowChanges -> CInt
wc_x WindowChanges
wc
{-# LINE 891 "Graphics/X11/Xlib/Extras.hsc" #-}
        (\Ptr WindowChanges
hsc_ptr -> Ptr WindowChanges -> Int -> CInt -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr WindowChanges
hsc_ptr Int
4) Ptr WindowChanges
p (CInt -> IO ()) -> CInt -> IO ()
forall a b. (a -> b) -> a -> b
$ WindowChanges -> CInt
wc_y WindowChanges
wc
{-# LINE 892 "Graphics/X11/Xlib/Extras.hsc" #-}
        (\Ptr WindowChanges
hsc_ptr -> Ptr WindowChanges -> Int -> CInt -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr WindowChanges
hsc_ptr Int
8) Ptr WindowChanges
p (CInt -> IO ()) -> CInt -> IO ()
forall a b. (a -> b) -> a -> b
$ WindowChanges -> CInt
wc_width WindowChanges
wc
{-# LINE 893 "Graphics/X11/Xlib/Extras.hsc" #-}
        (\Ptr WindowChanges
hsc_ptr -> Ptr WindowChanges -> Int -> CInt -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr WindowChanges
hsc_ptr Int
12) Ptr WindowChanges
p (CInt -> IO ()) -> CInt -> IO ()
forall a b. (a -> b) -> a -> b
$ WindowChanges -> CInt
wc_height WindowChanges
wc
{-# LINE 894 "Graphics/X11/Xlib/Extras.hsc" #-}
        (\Ptr WindowChanges
hsc_ptr -> Ptr WindowChanges -> Int -> CInt -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr WindowChanges
hsc_ptr Int
16) Ptr WindowChanges
p (CInt -> IO ()) -> CInt -> IO ()
forall a b. (a -> b) -> a -> b
$ WindowChanges -> CInt
wc_border_width WindowChanges
wc
{-# LINE 895 "Graphics/X11/Xlib/Extras.hsc" #-}
        (\Ptr WindowChanges
hsc_ptr -> Ptr WindowChanges -> Int -> Window -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr WindowChanges
hsc_ptr Int
24) Ptr WindowChanges
p (Window -> IO ()) -> Window -> IO ()
forall a b. (a -> b) -> a -> b
$ WindowChanges -> Window
wc_sibling WindowChanges
wc
{-# LINE 896 "Graphics/X11/Xlib/Extras.hsc" #-}
        (\Ptr WindowChanges
hsc_ptr -> Ptr WindowChanges -> Int -> CInt -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr WindowChanges
hsc_ptr Int
32) Ptr WindowChanges
p (CInt -> IO ()) -> CInt -> IO ()
forall a b. (a -> b) -> a -> b
$ WindowChanges -> CInt
wc_stack_mode WindowChanges
wc
{-# LINE 897 "Graphics/X11/Xlib/Extras.hsc" #-}

    peek :: Ptr WindowChanges -> IO WindowChanges
peek Ptr WindowChanges
p = (CInt
 -> CInt -> CInt -> CInt -> CInt -> Window -> CInt -> WindowChanges)
-> IO
     (CInt
      -> CInt -> CInt -> CInt -> CInt -> Window -> CInt -> WindowChanges)
forall (m :: * -> *) a. Monad m => a -> m a
return CInt
-> CInt -> CInt -> CInt -> CInt -> Window -> CInt -> WindowChanges
WindowChanges
                IO
  (CInt
   -> CInt -> CInt -> CInt -> CInt -> Window -> CInt -> WindowChanges)
-> IO CInt
-> IO
     (CInt -> CInt -> CInt -> CInt -> Window -> CInt -> WindowChanges)
forall (m :: * -> *) a b. Monad m => m (a -> b) -> m a -> m b
`ap` ((\Ptr WindowChanges
hsc_ptr -> Ptr WindowChanges -> Int -> IO CInt
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr WindowChanges
hsc_ptr Int
0) Ptr WindowChanges
p)
{-# LINE 900 "Graphics/X11/Xlib/Extras.hsc" #-}
                IO
  (CInt -> CInt -> CInt -> CInt -> Window -> CInt -> WindowChanges)
-> IO CInt
-> IO (CInt -> CInt -> CInt -> Window -> CInt -> WindowChanges)
forall (m :: * -> *) a b. Monad m => m (a -> b) -> m a -> m b
`ap` ((\Ptr WindowChanges
hsc_ptr -> Ptr WindowChanges -> Int -> IO CInt
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr WindowChanges
hsc_ptr Int
4) Ptr WindowChanges
p)
{-# LINE 901 "Graphics/X11/Xlib/Extras.hsc" #-}
                IO (CInt -> CInt -> CInt -> Window -> CInt -> WindowChanges)
-> IO CInt -> IO (CInt -> CInt -> Window -> CInt -> WindowChanges)
forall (m :: * -> *) a b. Monad m => m (a -> b) -> m a -> m b
`ap` ((\Ptr WindowChanges
hsc_ptr -> Ptr WindowChanges -> Int -> IO CInt
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr WindowChanges
hsc_ptr Int
8) Ptr WindowChanges
p)
{-# LINE 902 "Graphics/X11/Xlib/Extras.hsc" #-}
                IO (CInt -> CInt -> Window -> CInt -> WindowChanges)
-> IO CInt -> IO (CInt -> Window -> CInt -> WindowChanges)
forall (m :: * -> *) a b. Monad m => m (a -> b) -> m a -> m b
`ap` ((\Ptr WindowChanges
hsc_ptr -> Ptr WindowChanges -> Int -> IO CInt
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr WindowChanges
hsc_ptr Int
12) Ptr WindowChanges
p)
{-# LINE 903 "Graphics/X11/Xlib/Extras.hsc" #-}
                IO (CInt -> Window -> CInt -> WindowChanges)
-> IO CInt -> IO (Window -> CInt -> WindowChanges)
forall (m :: * -> *) a b. Monad m => m (a -> b) -> m a -> m b
`ap` ((\Ptr WindowChanges
hsc_ptr -> Ptr WindowChanges -> Int -> IO CInt
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr WindowChanges
hsc_ptr Int
16) Ptr WindowChanges
p)
{-# LINE 904 "Graphics/X11/Xlib/Extras.hsc" #-}
                IO (Window -> CInt -> WindowChanges)
-> IO Window -> IO (CInt -> WindowChanges)
forall (m :: * -> *) a b. Monad m => m (a -> b) -> m a -> m b
`ap` ((\Ptr WindowChanges
hsc_ptr -> Ptr WindowChanges -> Int -> IO Window
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr WindowChanges
hsc_ptr Int
24) Ptr WindowChanges
p)
{-# LINE 905 "Graphics/X11/Xlib/Extras.hsc" #-}
                IO (CInt -> WindowChanges) -> IO CInt -> IO WindowChanges
forall (m :: * -> *) a b. Monad m => m (a -> b) -> m a -> m b
`ap` ((\Ptr WindowChanges
hsc_ptr -> Ptr WindowChanges -> Int -> IO CInt
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr WindowChanges
hsc_ptr Int
32) Ptr WindowChanges
p)
{-# LINE 906 "Graphics/X11/Xlib/Extras.hsc" #-}

--
-- Some extra constants
--

none :: XID
none :: Window
none = Window
0
{-# LINE 913 "Graphics/X11/Xlib/Extras.hsc" #-}

anyButton :: Button
anyButton :: EventType
anyButton = EventType
0
{-# LINE 916 "Graphics/X11/Xlib/Extras.hsc" #-}

anyKey :: KeyCode
anyKey :: KeyCode
anyKey = Int -> KeyCode
forall a. Enum a => Int -> a
toEnum Int
0
{-# LINE 919 "Graphics/X11/Xlib/Extras.hsc" #-}

currentTime :: Time
currentTime :: Window
currentTime = Window
0
{-# LINE 922 "Graphics/X11/Xlib/Extras.hsc" #-}

--
-- The use of Int rather than CInt isn't 64 bit clean.
--

foreign import ccall unsafe "XlibExtras.h XConfigureWindow"
    xConfigureWindow :: Display -> Window -> CULong -> Ptr WindowChanges -> IO CInt

foreign import ccall unsafe "XlibExtras.h XKillClient"
    killClient :: Display -> Window -> IO CInt

configureWindow :: Display -> Window -> CULong -> WindowChanges -> IO ()
configureWindow :: Display -> Window -> CULong -> WindowChanges -> IO ()
configureWindow Display
d Window
w CULong
m WindowChanges
c = do
    CInt
_ <- WindowChanges -> (Ptr WindowChanges -> IO CInt) -> IO CInt
forall a b. Storable a => a -> (Ptr a -> IO b) -> IO b
with WindowChanges
c (Display -> Window -> CULong -> Ptr WindowChanges -> IO CInt
xConfigureWindow Display
d Window
w CULong
m)
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

foreign import ccall unsafe "XlibExtras.h XQueryTree"
    xQueryTree :: Display -> Window -> Ptr Window -> Ptr Window -> Ptr (Ptr Window) -> Ptr CInt -> IO Status

queryTree :: Display -> Window -> IO (Window, Window, [Window])
queryTree :: Display -> Window -> IO (Window, Window, [Window])
queryTree Display
d Window
w =
    (Ptr Window -> IO (Window, Window, [Window]))
-> IO (Window, Window, [Window])
forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca ((Ptr Window -> IO (Window, Window, [Window]))
 -> IO (Window, Window, [Window]))
-> (Ptr Window -> IO (Window, Window, [Window]))
-> IO (Window, Window, [Window])
forall a b. (a -> b) -> a -> b
$ \Ptr Window
root_return ->
    (Ptr Window -> IO (Window, Window, [Window]))
-> IO (Window, Window, [Window])
forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca ((Ptr Window -> IO (Window, Window, [Window]))
 -> IO (Window, Window, [Window]))
-> (Ptr Window -> IO (Window, Window, [Window]))
-> IO (Window, Window, [Window])
forall a b. (a -> b) -> a -> b
$ \Ptr Window
parent_return ->
    (Ptr (Ptr Window) -> IO (Window, Window, [Window]))
-> IO (Window, Window, [Window])
forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca ((Ptr (Ptr Window) -> IO (Window, Window, [Window]))
 -> IO (Window, Window, [Window]))
-> (Ptr (Ptr Window) -> IO (Window, Window, [Window]))
-> IO (Window, Window, [Window])
forall a b. (a -> b) -> a -> b
$ \Ptr (Ptr Window)
children_return ->
    (Ptr CInt -> IO (Window, Window, [Window]))
-> IO (Window, Window, [Window])
forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca ((Ptr CInt -> IO (Window, Window, [Window]))
 -> IO (Window, Window, [Window]))
-> (Ptr CInt -> IO (Window, Window, [Window]))
-> IO (Window, Window, [Window])
forall a b. (a -> b) -> a -> b
$ \Ptr CInt
nchildren_return -> do
        ()
_ <- String -> IO CInt -> IO ()
throwIfZero String
"queryTree" (IO CInt -> IO ()) -> IO CInt -> IO ()
forall a b. (a -> b) -> a -> b
$ Display
-> Window
-> Ptr Window
-> Ptr Window
-> Ptr (Ptr Window)
-> Ptr CInt
-> IO CInt
xQueryTree Display
d Window
w Ptr Window
root_return Ptr Window
parent_return Ptr (Ptr Window)
children_return Ptr CInt
nchildren_return
        Ptr Window
p <- Ptr (Ptr Window) -> IO (Ptr Window)
forall a. Storable a => Ptr a -> IO a
peek Ptr (Ptr Window)
children_return
        Int
n <- (CInt -> Int) -> IO CInt -> IO Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap CInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (IO CInt -> IO Int) -> IO CInt -> IO Int
forall a b. (a -> b) -> a -> b
$ Ptr CInt -> IO CInt
forall a. Storable a => Ptr a -> IO a
peek Ptr CInt
nchildren_return
        [Window]
ws <- Int -> Ptr Window -> IO [Window]
forall a. Storable a => Int -> Ptr a -> IO [a]
peekArray Int
n Ptr Window
p
        CInt
_ <- Ptr Window -> IO CInt
forall a. Ptr a -> IO CInt
xFree Ptr Window
p
        (Window -> Window -> [Window] -> (Window, Window, [Window]))
-> IO Window
-> IO Window
-> IO [Window]
-> IO (Window, Window, [Window])
forall (m :: * -> *) a1 a2 a3 r.
Monad m =>
(a1 -> a2 -> a3 -> r) -> m a1 -> m a2 -> m a3 -> m r
liftM3 (,,) (Ptr Window -> IO Window
forall a. Storable a => Ptr a -> IO a
peek Ptr Window
root_return) (Ptr Window -> IO Window
forall a. Storable a => Ptr a -> IO a
peek Ptr Window
parent_return) ([Window] -> IO [Window]
forall (m :: * -> *) a. Monad m => a -> m a
return [Window]
ws)

-- TODO: this data type is incomplete wrt. the C struct
data WindowAttributes = WindowAttributes
            { WindowAttributes -> CInt
wa_x, WindowAttributes -> CInt
wa_y, WindowAttributes -> CInt
wa_width, WindowAttributes -> CInt
wa_height, WindowAttributes -> CInt
wa_border_width :: CInt
            , WindowAttributes -> Window
wa_colormap :: Colormap
            , WindowAttributes -> Bool
wa_map_installed :: Bool
            , WindowAttributes -> CInt
wa_map_state :: CInt
            , WindowAttributes -> Window
wa_all_event_masks :: EventMask
            , WindowAttributes -> Window
wa_your_event_mask :: EventMask
            , WindowAttributes -> Window
wa_do_not_propagate_mask :: EventMask
            , WindowAttributes -> Bool
wa_override_redirect :: Bool
            }

--
-- possible map_states'
--
waIsUnmapped, waIsUnviewable, waIsViewable :: CInt
waIsUnmapped :: CInt
waIsUnmapped   = CInt -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral ( CInt
0   :: CInt )  -- 0
{-# LINE 971 "Graphics/X11/Xlib/Extras.hsc" #-}
waIsUnviewable = fromIntegral ( 1 :: CInt )  -- 1
{-# LINE 972 "Graphics/X11/Xlib/Extras.hsc" #-}
waIsViewable   = fromIntegral ( 2   :: CInt )  -- 2
{-# LINE 973 "Graphics/X11/Xlib/Extras.hsc" #-}

instance Storable WindowAttributes where
    -- this might be incorrect
    alignment :: WindowAttributes -> Int
alignment WindowAttributes
_ = CInt -> Int
forall a. Storable a => a -> Int
alignment (CInt
forall a. HasCallStack => a
undefined :: CInt)
    sizeOf :: WindowAttributes -> Int
sizeOf WindowAttributes
_ = (Int
136)
{-# LINE 978 "Graphics/X11/Xlib/Extras.hsc" #-}
    peek p = return WindowAttributes
                `ap` ((\hsc_ptr -> peekByteOff hsc_ptr 0) p)
{-# LINE 980 "Graphics/X11/Xlib/Extras.hsc" #-}
                `ap` ((\hsc_ptr -> peekByteOff hsc_ptr 4) p)
{-# LINE 981 "Graphics/X11/Xlib/Extras.hsc" #-}
                `ap` ((\hsc_ptr -> peekByteOff hsc_ptr 8) p)
{-# LINE 982 "Graphics/X11/Xlib/Extras.hsc" #-}
                `ap` ((\hsc_ptr -> peekByteOff hsc_ptr 12) p)
{-# LINE 983 "Graphics/X11/Xlib/Extras.hsc" #-}
                `ap` ((\hsc_ptr -> peekByteOff hsc_ptr 16) p)
{-# LINE 984 "Graphics/X11/Xlib/Extras.hsc" #-}
                `ap` ((\hsc_ptr -> peekByteOff hsc_ptr 80) p)
{-# LINE 985 "Graphics/X11/Xlib/Extras.hsc" #-}
                `ap` ((\hsc_ptr -> peekByteOff hsc_ptr 88) p)
{-# LINE 986 "Graphics/X11/Xlib/Extras.hsc" #-}
                `ap` ((\hsc_ptr -> peekByteOff hsc_ptr 92) p)
{-# LINE 987 "Graphics/X11/Xlib/Extras.hsc" #-}
                `ap` ((\hsc_ptr -> peekByteOff hsc_ptr 96) p)
{-# LINE 988 "Graphics/X11/Xlib/Extras.hsc" #-}
                `ap` ((\hsc_ptr -> peekByteOff hsc_ptr 104) p)
{-# LINE 989 "Graphics/X11/Xlib/Extras.hsc" #-}
                `ap` ((\hsc_ptr -> peekByteOff hsc_ptr 112) p)
{-# LINE 990 "Graphics/X11/Xlib/Extras.hsc" #-}
                `ap` ((\hsc_ptr -> peekByteOff hsc_ptr 120) p)
{-# LINE 991 "Graphics/X11/Xlib/Extras.hsc" #-}
    poke p wa = do
        (\hsc_ptr -> pokeByteOff hsc_ptr 0) p $ wa_x wa
{-# LINE 993 "Graphics/X11/Xlib/Extras.hsc" #-}
        (\hsc_ptr -> pokeByteOff hsc_ptr 4) p $ wa_y wa
{-# LINE 994 "Graphics/X11/Xlib/Extras.hsc" #-}
        (\hsc_ptr -> pokeByteOff hsc_ptr 8) p $ wa_width wa
{-# LINE 995 "Graphics/X11/Xlib/Extras.hsc" #-}
        (\hsc_ptr -> pokeByteOff hsc_ptr 12) p $ wa_height wa
{-# LINE 996 "Graphics/X11/Xlib/Extras.hsc" #-}
        (\hsc_ptr -> pokeByteOff hsc_ptr 16) p $ wa_border_width wa
{-# LINE 997 "Graphics/X11/Xlib/Extras.hsc" #-}
        (\hsc_ptr -> pokeByteOff hsc_ptr 80) p $ wa_colormap wa
{-# LINE 998 "Graphics/X11/Xlib/Extras.hsc" #-}
        (\hsc_ptr -> pokeByteOff hsc_ptr 88) p $ wa_map_installed wa
{-# LINE 999 "Graphics/X11/Xlib/Extras.hsc" #-}
        (\hsc_ptr -> pokeByteOff hsc_ptr 92) p $ wa_map_state wa
{-# LINE 1000 "Graphics/X11/Xlib/Extras.hsc" #-}
        (\hsc_ptr -> pokeByteOff hsc_ptr 96) p $ wa_all_event_masks wa
{-# LINE 1001 "Graphics/X11/Xlib/Extras.hsc" #-}
        (\hsc_ptr -> pokeByteOff hsc_ptr 104) p $ wa_your_event_mask wa
{-# LINE 1002 "Graphics/X11/Xlib/Extras.hsc" #-}
        (\hsc_ptr -> pokeByteOff hsc_ptr 112) p $ wa_do_not_propagate_mask wa
{-# LINE 1003 "Graphics/X11/Xlib/Extras.hsc" #-}
        (\hsc_ptr -> pokeByteOff hsc_ptr 120) p $ wa_override_redirect wa
{-# LINE 1004 "Graphics/X11/Xlib/Extras.hsc" #-}

foreign import ccall unsafe "XlibExtras.h XGetWindowAttributes"
    xGetWindowAttributes :: Display -> Window -> Ptr (WindowAttributes) -> IO Status

getWindowAttributes :: Display -> Window -> IO WindowAttributes
getWindowAttributes :: Display -> Window -> IO WindowAttributes
getWindowAttributes Display
d Window
w = (Ptr WindowAttributes -> IO WindowAttributes)
-> IO WindowAttributes
forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca ((Ptr WindowAttributes -> IO WindowAttributes)
 -> IO WindowAttributes)
-> (Ptr WindowAttributes -> IO WindowAttributes)
-> IO WindowAttributes
forall a b. (a -> b) -> a -> b
$ \Ptr WindowAttributes
p -> do
    ()
_ <- String -> IO CInt -> IO ()
throwIfZero String
"getWindowAttributes" (IO CInt -> IO ()) -> IO CInt -> IO ()
forall a b. (a -> b) -> a -> b
$ Display -> Window -> Ptr WindowAttributes -> IO CInt
xGetWindowAttributes Display
d Window
w Ptr WindowAttributes
p
    Ptr WindowAttributes -> IO WindowAttributes
forall a. Storable a => Ptr a -> IO a
peek Ptr WindowAttributes
p

-- | interface to the X11 library function @XChangeWindowAttributes()@.
foreign import ccall unsafe "XlibExtras.h XChangeWindowAttributes"
        changeWindowAttributes :: Display -> Window -> AttributeMask -> Ptr SetWindowAttributes -> IO ()

-- | Run an action with the server
withServer :: Display -> IO () -> IO ()
withServer :: Display -> IO () -> IO ()
withServer Display
dpy IO ()
f = do
    Display -> IO ()
grabServer Display
dpy
    IO ()
f
    Display -> IO ()
ungrabServer Display
dpy

data TextProperty = TextProperty {
        TextProperty -> CString
tp_value    :: CString,
        TextProperty -> Window
tp_encoding :: Atom,
        TextProperty -> CInt
tp_format   :: CInt,
        TextProperty -> Window
tp_nitems   :: Word64
{-# LINE 1029 "Graphics/X11/Xlib/Extras.hsc" #-}
    }

instance Storable TextProperty where
    sizeOf :: TextProperty -> Int
sizeOf    TextProperty
_ = (Int
32)
{-# LINE 1033 "Graphics/X11/Xlib/Extras.hsc" #-}
    alignment _ = alignment (undefined :: Word64)
{-# LINE 1034 "Graphics/X11/Xlib/Extras.hsc" #-}
    peek p = TextProperty `fmap` (\hsc_ptr -> peekByteOff hsc_ptr 0) p
{-# LINE 1035 "Graphics/X11/Xlib/Extras.hsc" #-}
                          `ap`   (\hsc_ptr -> peekByteOff hsc_ptr 8) p
{-# LINE 1036 "Graphics/X11/Xlib/Extras.hsc" #-}
                          `ap`   (\hsc_ptr -> peekByteOff hsc_ptr 16) p
{-# LINE 1037 "Graphics/X11/Xlib/Extras.hsc" #-}
                          `ap`   (\hsc_ptr -> peekByteOff hsc_ptr 24) p
{-# LINE 1038 "Graphics/X11/Xlib/Extras.hsc" #-}
    poke p (TextProperty val enc fmt nitems) = do
        (\hsc_ptr -> pokeByteOff hsc_ptr 0) p val
{-# LINE 1040 "Graphics/X11/Xlib/Extras.hsc" #-}
        (\hsc_ptr -> pokeByteOff hsc_ptr 8) p enc
{-# LINE 1041 "Graphics/X11/Xlib/Extras.hsc" #-}
        (\hsc_ptr -> pokeByteOff hsc_ptr 16) p fmt
{-# LINE 1042 "Graphics/X11/Xlib/Extras.hsc" #-}
        (\hsc_ptr -> pokeByteOff hsc_ptr 24) p nitems
{-# LINE 1043 "Graphics/X11/Xlib/Extras.hsc" #-}

foreign import ccall unsafe "XlibExtras.h XGetTextProperty"
    xGetTextProperty :: Display -> Window -> Ptr TextProperty -> Atom -> IO Status

getTextProperty :: Display -> Window -> Atom -> IO TextProperty
getTextProperty :: Display -> Window -> Window -> IO TextProperty
getTextProperty Display
d Window
w Window
a =
    (Ptr TextProperty -> IO TextProperty) -> IO TextProperty
forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca ((Ptr TextProperty -> IO TextProperty) -> IO TextProperty)
-> (Ptr TextProperty -> IO TextProperty) -> IO TextProperty
forall a b. (a -> b) -> a -> b
$ \Ptr TextProperty
textp -> do
        CInt
_ <- (CInt -> Bool) -> (CInt -> String) -> IO CInt -> IO CInt
forall a. (a -> Bool) -> (a -> String) -> IO a -> IO a
throwIf (CInt
0CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
==) (String -> CInt -> String
forall a b. a -> b -> a
const String
"getTextProperty") (IO CInt -> IO CInt) -> IO CInt -> IO CInt
forall a b. (a -> b) -> a -> b
$ Display -> Window -> Ptr TextProperty -> Window -> IO CInt
xGetTextProperty Display
d Window
w Ptr TextProperty
textp Window
a
        Ptr TextProperty -> IO TextProperty
forall a. Storable a => Ptr a -> IO a
peek Ptr TextProperty
textp

foreign import ccall unsafe "XlibExtras.h XwcTextPropertyToTextList"
    xwcTextPropertyToTextList :: Display -> Ptr TextProperty -> Ptr (Ptr CWString) -> Ptr CInt -> IO CInt

wcTextPropertyToTextList :: Display -> TextProperty -> IO [String]
wcTextPropertyToTextList :: Display -> TextProperty -> IO [String]
wcTextPropertyToTextList Display
d TextProperty
prop =
    (Ptr (Ptr CWString) -> IO [String]) -> IO [String]
forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca    ((Ptr (Ptr CWString) -> IO [String]) -> IO [String])
-> (Ptr (Ptr CWString) -> IO [String]) -> IO [String]
forall a b. (a -> b) -> a -> b
$ \Ptr (Ptr CWString)
listp  ->
    (Ptr CInt -> IO [String]) -> IO [String]
forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca    ((Ptr CInt -> IO [String]) -> IO [String])
-> (Ptr CInt -> IO [String]) -> IO [String]
forall a b. (a -> b) -> a -> b
$ \Ptr CInt
countp ->
    TextProperty -> (Ptr TextProperty -> IO [String]) -> IO [String]
forall a b. Storable a => a -> (Ptr a -> IO b) -> IO b
with TextProperty
prop ((Ptr TextProperty -> IO [String]) -> IO [String])
-> (Ptr TextProperty -> IO [String]) -> IO [String]
forall a b. (a -> b) -> a -> b
$ \Ptr TextProperty
propp  -> do
        CInt
_ <- (CInt -> Bool) -> (CInt -> String) -> IO CInt -> IO CInt
forall a. (a -> Bool) -> (a -> String) -> IO a -> IO a
throwIf (CInt
successCInt -> CInt -> Bool
forall a. Ord a => a -> a -> Bool
>) (String -> CInt -> String
forall a b. a -> b -> a
const String
"wcTextPropertyToTextList") (IO CInt -> IO CInt) -> IO CInt -> IO CInt
forall a b. (a -> b) -> a -> b
$
            Display
-> Ptr TextProperty -> Ptr (Ptr CWString) -> Ptr CInt -> IO CInt
xwcTextPropertyToTextList Display
d Ptr TextProperty
propp Ptr (Ptr CWString)
listp Ptr CInt
countp
        CInt
count <- Ptr CInt -> IO CInt
forall a. Storable a => Ptr a -> IO a
peek Ptr CInt
countp
        Ptr CWString
list  <- Ptr (Ptr CWString) -> IO (Ptr CWString)
forall a. Storable a => Ptr a -> IO a
peek Ptr (Ptr CWString)
listp
        [String]
texts <- ((Int -> IO String) -> [Int] -> IO [String])
-> [Int] -> (Int -> IO String) -> IO [String]
forall a b c. (a -> b -> c) -> b -> a -> c
flip (Int -> IO String) -> [Int] -> IO [String]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM [Int
0..CInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral CInt
count Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1] ((Int -> IO String) -> IO [String])
-> (Int -> IO String) -> IO [String]
forall a b. (a -> b) -> a -> b
$ \Int
i ->
                     Ptr CWString -> Int -> IO CWString
forall a. Storable a => Ptr a -> Int -> IO a
peekElemOff Ptr CWString
list Int
i IO CWString -> (CWString -> IO String) -> IO String
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= CWString -> IO String
peekCWString
        Ptr CWString -> IO ()
wcFreeStringList Ptr CWString
list
        [String] -> IO [String]
forall (m :: * -> *) a. Monad m => a -> m a
return [String]
texts

foreign import ccall unsafe "XlibExtras.h XwcFreeStringList"
    wcFreeStringList :: Ptr CWString -> IO ()

newtype FontSet = FontSet (Ptr FontSet)
    deriving (FontSet -> FontSet -> Bool
(FontSet -> FontSet -> Bool)
-> (FontSet -> FontSet -> Bool) -> Eq FontSet
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FontSet -> FontSet -> Bool
$c/= :: FontSet -> FontSet -> Bool
== :: FontSet -> FontSet -> Bool
$c== :: FontSet -> FontSet -> Bool
Eq, Eq FontSet
Eq FontSet
-> (FontSet -> FontSet -> Ordering)
-> (FontSet -> FontSet -> Bool)
-> (FontSet -> FontSet -> Bool)
-> (FontSet -> FontSet -> Bool)
-> (FontSet -> FontSet -> Bool)
-> (FontSet -> FontSet -> FontSet)
-> (FontSet -> FontSet -> FontSet)
-> Ord FontSet
FontSet -> FontSet -> Bool
FontSet -> FontSet -> Ordering
FontSet -> FontSet -> FontSet
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 :: FontSet -> FontSet -> FontSet
$cmin :: FontSet -> FontSet -> FontSet
max :: FontSet -> FontSet -> FontSet
$cmax :: FontSet -> FontSet -> FontSet
>= :: FontSet -> FontSet -> Bool
$c>= :: FontSet -> FontSet -> Bool
> :: FontSet -> FontSet -> Bool
$c> :: FontSet -> FontSet -> Bool
<= :: FontSet -> FontSet -> Bool
$c<= :: FontSet -> FontSet -> Bool
< :: FontSet -> FontSet -> Bool
$c< :: FontSet -> FontSet -> Bool
compare :: FontSet -> FontSet -> Ordering
$ccompare :: FontSet -> FontSet -> Ordering
$cp1Ord :: Eq FontSet
Ord, Int -> FontSet -> ShowS
[FontSet] -> ShowS
FontSet -> String
(Int -> FontSet -> ShowS)
-> (FontSet -> String) -> ([FontSet] -> ShowS) -> Show FontSet
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [FontSet] -> ShowS
$cshowList :: [FontSet] -> ShowS
show :: FontSet -> String
$cshow :: FontSet -> String
showsPrec :: Int -> FontSet -> ShowS
$cshowsPrec :: Int -> FontSet -> ShowS
Show)

foreign import ccall unsafe "XlibExtras.h XCreateFontSet"
    xCreateFontSet :: Display -> CString -> Ptr (Ptr CString) -> Ptr CInt -> Ptr CString -> IO (Ptr FontSet)

createFontSet :: Display -> String -> IO ([String], String, FontSet)
createFontSet :: Display -> String -> IO ([String], String, FontSet)
createFontSet Display
d String
fn =
    String
-> (CString -> IO ([String], String, FontSet))
-> IO ([String], String, FontSet)
forall a. String -> (CString -> IO a) -> IO a
withCString String
fn ((CString -> IO ([String], String, FontSet))
 -> IO ([String], String, FontSet))
-> (CString -> IO ([String], String, FontSet))
-> IO ([String], String, FontSet)
forall a b. (a -> b) -> a -> b
$ \CString
fontp  ->
    (Ptr (Ptr CString) -> IO ([String], String, FontSet))
-> IO ([String], String, FontSet)
forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca         ((Ptr (Ptr CString) -> IO ([String], String, FontSet))
 -> IO ([String], String, FontSet))
-> (Ptr (Ptr CString) -> IO ([String], String, FontSet))
-> IO ([String], String, FontSet)
forall a b. (a -> b) -> a -> b
$ \Ptr (Ptr CString)
listp  ->
    (Ptr CInt -> IO ([String], String, FontSet))
-> IO ([String], String, FontSet)
forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca         ((Ptr CInt -> IO ([String], String, FontSet))
 -> IO ([String], String, FontSet))
-> (Ptr CInt -> IO ([String], String, FontSet))
-> IO ([String], String, FontSet)
forall a b. (a -> b) -> a -> b
$ \Ptr CInt
countp ->
    (Ptr CString -> IO ([String], String, FontSet))
-> IO ([String], String, FontSet)
forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca         ((Ptr CString -> IO ([String], String, FontSet))
 -> IO ([String], String, FontSet))
-> (Ptr CString -> IO ([String], String, FontSet))
-> IO ([String], String, FontSet)
forall a b. (a -> b) -> a -> b
$ \Ptr CString
defp   -> do
        Ptr FontSet
fs      <- String -> IO (Ptr FontSet) -> IO (Ptr FontSet)
forall a. String -> IO (Ptr a) -> IO (Ptr a)
throwIfNull String
"createFontSet" (IO (Ptr FontSet) -> IO (Ptr FontSet))
-> IO (Ptr FontSet) -> IO (Ptr FontSet)
forall a b. (a -> b) -> a -> b
$
                       Display
-> CString
-> Ptr (Ptr CString)
-> Ptr CInt
-> Ptr CString
-> IO (Ptr FontSet)
xCreateFontSet Display
d CString
fontp Ptr (Ptr CString)
listp Ptr CInt
countp Ptr CString
defp
        CInt
count   <- Ptr CInt -> IO CInt
forall a. Storable a => Ptr a -> IO a
peek Ptr CInt
countp
        Ptr CString
list    <- Ptr (Ptr CString) -> IO (Ptr CString)
forall a. Storable a => Ptr a -> IO a
peek Ptr (Ptr CString)
listp
        [String]
missing <- ((Int -> IO String) -> [Int] -> IO [String])
-> [Int] -> (Int -> IO String) -> IO [String]
forall a b c. (a -> b -> c) -> b -> a -> c
flip (Int -> IO String) -> [Int] -> IO [String]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM [Int
0..CInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral CInt
count Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1] ((Int -> IO String) -> IO [String])
-> (Int -> IO String) -> IO [String]
forall a b. (a -> b) -> a -> b
$ \Int
i ->
                       Ptr CString -> Int -> IO CString
forall a. Storable a => Ptr a -> Int -> IO a
peekElemOff Ptr CString
list Int
i IO CString -> (CString -> IO String) -> IO String
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= CString -> IO String
peekCString
        String
def     <- Ptr CString -> IO CString
forall a. Storable a => Ptr a -> IO a
peek Ptr CString
defp IO CString -> (CString -> IO String) -> IO String
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= CString -> IO String
peekCString
        Ptr CString -> IO ()
freeStringList Ptr CString
list
        ([String], String, FontSet) -> IO ([String], String, FontSet)
forall (m :: * -> *) a. Monad m => a -> m a
return ([String]
missing, String
def, Ptr FontSet -> FontSet
FontSet Ptr FontSet
fs)

foreign import ccall unsafe "XlibExtras.h XFreeStringList"
    freeStringList :: Ptr CString -> IO ()

foreign import ccall unsafe "XlibExtras.h XFreeFontSet"
    freeFontSet :: Display -> FontSet -> IO ()

foreign import ccall unsafe "XlibExtras.h XwcTextExtents"
    xwcTextExtents :: FontSet -> CWString -> CInt -> Ptr Rectangle -> Ptr Rectangle -> IO CInt

wcTextExtents :: FontSet -> String -> (Rectangle, Rectangle)
wcTextExtents :: FontSet -> String -> (Rectangle, Rectangle)
wcTextExtents FontSet
fs String
text = IO (Rectangle, Rectangle) -> (Rectangle, Rectangle)
forall a. IO a -> a
unsafePerformIO (IO (Rectangle, Rectangle) -> (Rectangle, Rectangle))
-> IO (Rectangle, Rectangle) -> (Rectangle, Rectangle)
forall a b. (a -> b) -> a -> b
$
    String
-> (CWStringLen -> IO (Rectangle, Rectangle))
-> IO (Rectangle, Rectangle)
forall a. String -> (CWStringLen -> IO a) -> IO a
withCWStringLen String
text ((CWStringLen -> IO (Rectangle, Rectangle))
 -> IO (Rectangle, Rectangle))
-> (CWStringLen -> IO (Rectangle, Rectangle))
-> IO (Rectangle, Rectangle)
forall a b. (a -> b) -> a -> b
$ \(CWString
textp, Int
len) ->
    (Ptr Rectangle -> IO (Rectangle, Rectangle))
-> IO (Rectangle, Rectangle)
forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca               ((Ptr Rectangle -> IO (Rectangle, Rectangle))
 -> IO (Rectangle, Rectangle))
-> (Ptr Rectangle -> IO (Rectangle, Rectangle))
-> IO (Rectangle, Rectangle)
forall a b. (a -> b) -> a -> b
$ \Ptr Rectangle
inkp          ->
    (Ptr Rectangle -> IO (Rectangle, Rectangle))
-> IO (Rectangle, Rectangle)
forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca               ((Ptr Rectangle -> IO (Rectangle, Rectangle))
 -> IO (Rectangle, Rectangle))
-> (Ptr Rectangle -> IO (Rectangle, Rectangle))
-> IO (Rectangle, Rectangle)
forall a b. (a -> b) -> a -> b
$ \Ptr Rectangle
logicalp      -> do
        CInt
_ <- FontSet
-> CWString -> CInt -> Ptr Rectangle -> Ptr Rectangle -> IO CInt
xwcTextExtents FontSet
fs CWString
textp (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
len) Ptr Rectangle
inkp Ptr Rectangle
logicalp
        (,) (Rectangle -> Rectangle -> (Rectangle, Rectangle))
-> IO Rectangle -> IO (Rectangle -> (Rectangle, Rectangle))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
`fmap` Ptr Rectangle -> IO Rectangle
forall a. Storable a => Ptr a -> IO a
peek Ptr Rectangle
inkp IO (Rectangle -> (Rectangle, Rectangle))
-> IO Rectangle -> IO (Rectangle, Rectangle)
forall (m :: * -> *) a b. Monad m => m (a -> b) -> m a -> m b
`ap` Ptr Rectangle -> IO Rectangle
forall a. Storable a => Ptr a -> IO a
peek Ptr Rectangle
logicalp

foreign import ccall unsafe "XlibExtras.h XwcDrawString"
    xwcDrawString :: Display -> Drawable -> FontSet -> GC -> Position -> Position -> CWString -> CInt -> IO ()

wcDrawString :: Display -> Drawable -> FontSet -> GC -> Position -> Position -> String -> IO ()
wcDrawString :: Display
-> Window
-> FontSet
-> GC
-> Position
-> Position
-> String
-> IO ()
wcDrawString Display
d Window
w FontSet
fs GC
gc Position
x Position
y =
    (String -> (CWStringLen -> IO ()) -> IO ())
-> (CWStringLen -> IO ()) -> String -> IO ()
forall a b c. (a -> b -> c) -> b -> a -> c
flip String -> (CWStringLen -> IO ()) -> IO ()
forall a. String -> (CWStringLen -> IO a) -> IO a
withCWStringLen ((CWStringLen -> IO ()) -> String -> IO ())
-> (CWStringLen -> IO ()) -> String -> IO ()
forall a b. (a -> b) -> a -> b
$ \(CWString
s, Int
len) ->
        Display
-> Window
-> FontSet
-> GC
-> Position
-> Position
-> CWString
-> CInt
-> IO ()
xwcDrawString Display
d Window
w FontSet
fs GC
gc Position
x Position
y CWString
s (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
len)

foreign import ccall unsafe "XlibExtras.h XwcDrawImageString"
    xwcDrawImageString :: Display -> Drawable -> FontSet -> GC -> Position -> Position -> CWString -> CInt -> IO ()

wcDrawImageString :: Display -> Drawable -> FontSet -> GC -> Position -> Position -> String -> IO ()
wcDrawImageString :: Display
-> Window
-> FontSet
-> GC
-> Position
-> Position
-> String
-> IO ()
wcDrawImageString Display
d Window
w FontSet
fs GC
gc Position
x Position
y =
    (String -> (CWStringLen -> IO ()) -> IO ())
-> (CWStringLen -> IO ()) -> String -> IO ()
forall a b c. (a -> b -> c) -> b -> a -> c
flip String -> (CWStringLen -> IO ()) -> IO ()
forall a. String -> (CWStringLen -> IO a) -> IO a
withCWStringLen ((CWStringLen -> IO ()) -> String -> IO ())
-> (CWStringLen -> IO ()) -> String -> IO ()
forall a b. (a -> b) -> a -> b
$ \(CWString
s, Int
len) ->
        Display
-> Window
-> FontSet
-> GC
-> Position
-> Position
-> CWString
-> CInt
-> IO ()
xwcDrawImageString Display
d Window
w FontSet
fs GC
gc Position
x Position
y CWString
s (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
len)

foreign import ccall unsafe "XlibExtras.h XwcTextEscapement"
    xwcTextEscapement :: FontSet -> CWString -> CInt -> IO Int32

wcTextEscapement :: FontSet -> String -> Int32
wcTextEscapement :: FontSet -> String -> Position
wcTextEscapement FontSet
font_set String
string = IO Position -> Position
forall a. IO a -> a
unsafePerformIO (IO Position -> Position) -> IO Position -> Position
forall a b. (a -> b) -> a -> b
$
    String -> (CWStringLen -> IO Position) -> IO Position
forall a. String -> (CWStringLen -> IO a) -> IO a
withCWStringLen String
string ((CWStringLen -> IO Position) -> IO Position)
-> (CWStringLen -> IO Position) -> IO Position
forall a b. (a -> b) -> a -> b
$ \ (CWString
c_string, Int
len) ->
    FontSet -> CWString -> CInt -> IO Position
xwcTextEscapement FontSet
font_set CWString
c_string (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
len)

foreign import ccall unsafe "XlibExtras.h XFetchName"
    xFetchName :: Display -> Window -> Ptr CString -> IO Status

fetchName :: Display -> Window -> IO (Maybe String)
fetchName :: Display -> Window -> IO (Maybe String)
fetchName Display
d Window
w = (Ptr CString -> IO (Maybe String)) -> IO (Maybe String)
forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca ((Ptr CString -> IO (Maybe String)) -> IO (Maybe String))
-> (Ptr CString -> IO (Maybe String)) -> IO (Maybe String)
forall a b. (a -> b) -> a -> b
$ \Ptr CString
p -> do
    CInt
_ <- Display -> Window -> Ptr CString -> IO CInt
xFetchName Display
d Window
w Ptr CString
p
    CString
cstr <- Ptr CString -> IO CString
forall a. Storable a => Ptr a -> IO a
peek Ptr CString
p
    if CString
cstr CString -> CString -> Bool
forall a. Eq a => a -> a -> Bool
== CString
forall b. Ptr b
nullPtr
        then Maybe String -> IO (Maybe String)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe String
forall a. Maybe a
Nothing
        else do
            String
str <- CString -> IO String
peekCString CString
cstr
            CInt
_ <- CString -> IO CInt
forall a. Ptr a -> IO CInt
xFree CString
cstr
            Maybe String -> IO (Maybe String)
forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe String -> IO (Maybe String))
-> Maybe String -> IO (Maybe String)
forall a b. (a -> b) -> a -> b
$ String -> Maybe String
forall a. a -> Maybe a
Just String
str

foreign import ccall unsafe "XlibExtras.h XGetTransientForHint"
    xGetTransientForHint :: Display -> Window -> Ptr Window -> IO Status

getTransientForHint :: Display -> Window -> IO (Maybe Window)
getTransientForHint :: Display -> Window -> IO (Maybe Window)
getTransientForHint Display
d Window
w = (Ptr Window -> IO (Maybe Window)) -> IO (Maybe Window)
forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca ((Ptr Window -> IO (Maybe Window)) -> IO (Maybe Window))
-> (Ptr Window -> IO (Maybe Window)) -> IO (Maybe Window)
forall a b. (a -> b) -> a -> b
$ \Ptr Window
wp -> do
    CInt
status <- Display -> Window -> Ptr Window -> IO CInt
xGetTransientForHint Display
d Window
w Ptr Window
wp
    if CInt
status CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
== CInt
0
        then Maybe Window -> IO (Maybe Window)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Window
forall a. Maybe a
Nothing
        else Window -> Maybe Window
forall a. a -> Maybe a
Just (Window -> Maybe Window) -> IO Window -> IO (Maybe Window)
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
`liftM` Ptr Window -> IO Window
forall a. Storable a => Ptr a -> IO a
peek Ptr Window
wp

------------------------------------------------------------------------
-- setWMProtocols :: Display -> Window -> [Atom] -> IO ()

{-
setWMProtocols :: Display -> Window -> [Atom] -> IO ()
setWMProtocols display w protocols =
    withArray protocols $ \ protocol_array ->
    xSetWMProtocols display w protocol_array (length protocols)
foreign import ccall unsafe "HsXlib.h XSetWMProtocols"
    xSetWMProtocols :: Display -> Window -> Ptr Atom -> CInt -> IO ()
-}

-- | The XGetWMProtocols function returns the list of atoms
-- stored in the WM_PROTOCOLS property on the specified window.
-- These atoms describe window manager protocols in
-- which the owner of this window is willing to participate.
-- If the property exists, is of type ATOM, is of format 32,
-- and the atom WM_PROTOCOLS can be interned, XGetWMProtocols
-- sets the protocols_return argument to a list of atoms,
-- sets the count_return argument to the number of elements
-- in the list, and returns a nonzero status.  Otherwise, it
-- sets neither of the return arguments and returns a zero
-- status.  To release the list of atoms, use XFree.
--
getWMProtocols :: Display -> Window -> IO [Atom]
getWMProtocols :: Display -> Window -> IO [Window]
getWMProtocols Display
display Window
w = do
    (Ptr (Ptr Window) -> IO [Window]) -> IO [Window]
forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca ((Ptr (Ptr Window) -> IO [Window]) -> IO [Window])
-> (Ptr (Ptr Window) -> IO [Window]) -> IO [Window]
forall a b. (a -> b) -> a -> b
$ \Ptr (Ptr Window)
atom_ptr_ptr ->
      (Ptr CInt -> IO [Window]) -> IO [Window]
forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca ((Ptr CInt -> IO [Window]) -> IO [Window])
-> (Ptr CInt -> IO [Window]) -> IO [Window]
forall a b. (a -> b) -> a -> b
$ \Ptr CInt
count_ptr -> do

       CInt
st <- Display -> Window -> Ptr (Ptr Window) -> Ptr CInt -> IO CInt
xGetWMProtocols Display
display Window
w Ptr (Ptr Window)
atom_ptr_ptr Ptr CInt
count_ptr
       if CInt
st CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
== CInt
0
            then [Window] -> IO [Window]
forall (m :: * -> *) a. Monad m => a -> m a
return []
            else do CInt
sz       <- Ptr CInt -> IO CInt
forall a. Storable a => Ptr a -> IO a
peek Ptr CInt
count_ptr
                    Ptr Window
atom_ptr <- Ptr (Ptr Window) -> IO (Ptr Window)
forall a. Storable a => Ptr a -> IO a
peek Ptr (Ptr Window)
atom_ptr_ptr
                    [Window]
atoms    <- Int -> Ptr Window -> IO [Window]
forall a. Storable a => Int -> Ptr a -> IO [a]
peekArray (CInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral CInt
sz) Ptr Window
atom_ptr
                    CInt
_ <- Ptr Window -> IO CInt
forall a. Ptr a -> IO CInt
xFree Ptr Window
atom_ptr
                    [Window] -> IO [Window]
forall (m :: * -> *) a. Monad m => a -> m a
return [Window]
atoms

foreign import ccall unsafe "HsXlib.h XGetWMProtocols"
    xGetWMProtocols :: Display -> Window -> Ptr (Ptr Atom) -> Ptr CInt -> IO Status


------------------------------------------------------------------------
-- Creating events

setEventType :: XEventPtr -> EventType -> IO ()
setEventType :: XEventPtr -> EventType -> IO ()
setEventType = (\XEventPtr
hsc_ptr -> XEventPtr -> Int -> EventType -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff XEventPtr
hsc_ptr Int
0)
{-# LINE 1207 "Graphics/X11/Xlib/Extras.hsc" #-}

{-
typedef struct {
        int type;               /* SelectionNotify */
        unsigned long serial;   /* # of last request processed by server */
        Bool send_event;        /* true if this came from a SendEvent request */
        Display *display;       /* Display the event was read from */
        Window requestor;
        Atom selection;
        Atom target;
        Atom property;          /* atom or None */
        Time time;
} XSelectionEvent;
-}

setSelectionNotify :: XEventPtr -> Window -> Atom -> Atom -> Atom -> Time -> IO ()
setSelectionNotify :: XEventPtr
-> Window -> Window -> Window -> Window -> Window -> IO ()
setSelectionNotify XEventPtr
p Window
requestor Window
selection Window
target Window
property Window
time = do
    XEventPtr -> EventType -> IO ()
setEventType XEventPtr
p EventType
selectionNotify
    (\XEventPtr
hsc_ptr -> XEventPtr -> Int -> Window -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff XEventPtr
hsc_ptr Int
32)    XEventPtr
p Window
requestor
{-# LINE 1226 "Graphics/X11/Xlib/Extras.hsc" #-}
    (\hsc_ptr -> pokeByteOff hsc_ptr 40)    p selection
{-# LINE 1227 "Graphics/X11/Xlib/Extras.hsc" #-}
    (\hsc_ptr -> pokeByteOff hsc_ptr 48)       p target
{-# LINE 1228 "Graphics/X11/Xlib/Extras.hsc" #-}
    (\hsc_ptr -> pokeByteOff hsc_ptr 56)     p property
{-# LINE 1229 "Graphics/X11/Xlib/Extras.hsc" #-}
    (\hsc_ptr -> pokeByteOff hsc_ptr 64)         p time
{-# LINE 1230 "Graphics/X11/Xlib/Extras.hsc" #-}

-- hacky way to set up an XClientMessageEvent
-- Should have a Storable instance for XEvent/Event?
setClientMessageEvent :: XEventPtr -> Window -> Atom -> CInt -> Atom -> Time -> IO ()
setClientMessageEvent :: XEventPtr -> Window -> Window -> CInt -> Window -> Window -> IO ()
setClientMessageEvent XEventPtr
p Window
window Window
message_type CInt
format Window
l_0_ Window
l_1_ = do
    XEventPtr -> Window -> Window -> CInt -> [CInt] -> IO ()
setClientMessageEvent' XEventPtr
p Window
window Window
message_type CInt
format [Window -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Window
l_0_, Window -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Window
l_1_]

-- slightly less hacky way to set up an XClientMessageEvent
setClientMessageEvent' :: XEventPtr -> Window -> Atom -> CInt -> [CInt] -> IO ()
setClientMessageEvent' :: XEventPtr -> Window -> Window -> CInt -> [CInt] -> IO ()
setClientMessageEvent' XEventPtr
p Window
window Window
message_type CInt
format [CInt]
dat = do
    (\XEventPtr
hsc_ptr -> XEventPtr -> Int -> Window -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff XEventPtr
hsc_ptr Int
32)         XEventPtr
p Window
window
{-# LINE 1241 "Graphics/X11/Xlib/Extras.hsc" #-}
    (\hsc_ptr -> pokeByteOff hsc_ptr 40)   p message_type
{-# LINE 1242 "Graphics/X11/Xlib/Extras.hsc" #-}
    (\hsc_ptr -> pokeByteOff hsc_ptr 48)         p format
{-# LINE 1243 "Graphics/X11/Xlib/Extras.hsc" #-}
    case format of
        8  -> do let datap = (\hsc_ptr -> hsc_ptr `plusPtr` 56) p :: Ptr Word8
{-# LINE 1245 "Graphics/X11/Xlib/Extras.hsc" #-}
                 pokeArray datap $ take 20 $ map fromIntegral dat ++ repeat 0
        16 -> do let datap = (\hsc_ptr -> hsc_ptr `plusPtr` 56) p :: Ptr Word16
{-# LINE 1247 "Graphics/X11/Xlib/Extras.hsc" #-}
                 pokeArray datap $ take 10 $ map fromIntegral dat ++ repeat 0
        32 -> do let datap = (\hsc_ptr -> hsc_ptr `plusPtr` 56) p :: Ptr CLong
{-# LINE 1249 "Graphics/X11/Xlib/Extras.hsc" #-}
                 pokeArray datap $ take 5  $ map fromIntegral dat ++ repeat 0
        _  -> error "X11.Extras.setClientMessageEvent': illegal format"

setConfigureEvent :: XEventPtr -> Window -> Window -> CInt -> CInt -> CInt -> CInt -> CInt -> Window -> Bool -> IO ()
setConfigureEvent :: XEventPtr
-> Window
-> Window
-> CInt
-> CInt
-> CInt
-> CInt
-> CInt
-> Window
-> Bool
-> IO ()
setConfigureEvent XEventPtr
p Window
ev Window
win CInt
x CInt
y CInt
w CInt
h CInt
bw Window
abv Bool
org = do
    (\XEventPtr
hsc_ptr -> XEventPtr -> Int -> Window -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff XEventPtr
hsc_ptr Int
32) XEventPtr
p Window
ev
{-# LINE 1255 "Graphics/X11/Xlib/Extras.hsc" #-}
    (\hsc_ptr -> pokeByteOff hsc_ptr 40) p win
{-# LINE 1256 "Graphics/X11/Xlib/Extras.hsc" #-}
    (\hsc_ptr -> pokeByteOff hsc_ptr 48) p x
{-# LINE 1257 "Graphics/X11/Xlib/Extras.hsc" #-}
    (\hsc_ptr -> pokeByteOff hsc_ptr 52) p y
{-# LINE 1258 "Graphics/X11/Xlib/Extras.hsc" #-}
    (\hsc_ptr -> pokeByteOff hsc_ptr 56) p w
{-# LINE 1259 "Graphics/X11/Xlib/Extras.hsc" #-}
    (\hsc_ptr -> pokeByteOff hsc_ptr 60) p h
{-# LINE 1260 "Graphics/X11/Xlib/Extras.hsc" #-}
    (\hsc_ptr -> pokeByteOff hsc_ptr 64) p bw
{-# LINE 1261 "Graphics/X11/Xlib/Extras.hsc" #-}
    (\hsc_ptr -> pokeByteOff hsc_ptr 72) p abv
{-# LINE 1262 "Graphics/X11/Xlib/Extras.hsc" #-}
    (\hsc_ptr -> pokeByteOff hsc_ptr 80) p (if org then 1 else 0 :: CInt)
{-# LINE 1263 "Graphics/X11/Xlib/Extras.hsc" #-}

setKeyEvent :: XEventPtr -> Window -> Window -> Window -> KeyMask -> KeyCode -> Bool -> IO ()
setKeyEvent :: XEventPtr
-> Window
-> Window
-> Window
-> KeyMask
-> KeyCode
-> Bool
-> IO ()
setKeyEvent XEventPtr
p Window
win Window
root Window
subwin KeyMask
state KeyCode
keycode Bool
sameScreen = do
    (\XEventPtr
hsc_ptr -> XEventPtr -> Int -> Window -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff XEventPtr
hsc_ptr Int
32) XEventPtr
p Window
win
{-# LINE 1267 "Graphics/X11/Xlib/Extras.hsc" #-}
    (\hsc_ptr -> pokeByteOff hsc_ptr 40) p root
{-# LINE 1268 "Graphics/X11/Xlib/Extras.hsc" #-}
    (\hsc_ptr -> pokeByteOff hsc_ptr 48) p subwin
{-# LINE 1269 "Graphics/X11/Xlib/Extras.hsc" #-}
    (\hsc_ptr -> pokeByteOff hsc_ptr 56) p currentTime
{-# LINE 1270 "Graphics/X11/Xlib/Extras.hsc" #-}
    (\hsc_ptr -> pokeByteOff hsc_ptr 64) p (1 :: CInt)
{-# LINE 1271 "Graphics/X11/Xlib/Extras.hsc" #-}
    (\hsc_ptr -> pokeByteOff hsc_ptr 68) p (1 :: CInt)
{-# LINE 1272 "Graphics/X11/Xlib/Extras.hsc" #-}
    (\hsc_ptr -> pokeByteOff hsc_ptr 72) p (1 :: CInt)
{-# LINE 1273 "Graphics/X11/Xlib/Extras.hsc" #-}
    (\hsc_ptr -> pokeByteOff hsc_ptr 76) p (1 :: CInt)
{-# LINE 1274 "Graphics/X11/Xlib/Extras.hsc" #-}
    (\hsc_ptr -> pokeByteOff hsc_ptr 80) p state
{-# LINE 1275 "Graphics/X11/Xlib/Extras.hsc" #-}
    (\hsc_ptr -> pokeByteOff hsc_ptr 84) p keycode
{-# LINE 1276 "Graphics/X11/Xlib/Extras.hsc" #-}
    (\hsc_ptr -> pokeByteOff hsc_ptr 88) p sameScreen
{-# LINE 1277 "Graphics/X11/Xlib/Extras.hsc" #-}
    return ()

{-
       typedef struct {
            int type;                /* ClientMessage */
            unsigned long serial;    /* # of last request processed by server */
            Bool send_event;         /* true if this came from a SendEvent request */
            Display *display;        /* Display the event was read from */
            Window window;
            Atom message_type;
            int format;
            union {
                 char b[20];
                 short s[10];
                 long l[5];
                    } data;
       } XClientMessageEvent;

-}

------------------------------------------------------------------------
-- XErrorEvents
--
-- I'm too lazy to write the binding
--

foreign import ccall unsafe "XlibExtras.h x11_extras_set_error_handler"
    xSetErrorHandler   :: IO ()

-- | refreshKeyboardMapping.  TODO Remove this binding when the fix has been commited to
-- X11
refreshKeyboardMapping :: Event -> IO ()
refreshKeyboardMapping :: Event -> IO ()
refreshKeyboardMapping ev :: Event
ev@(MappingNotifyEvent {ev_event_display :: Event -> Display
ev_event_display = (Display Ptr Display
d)})
 = Int -> (Ptr () -> IO ()) -> IO ()
forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes (Int
56) ((Ptr () -> IO ()) -> IO ()) -> (Ptr () -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr ()
p -> do
{-# LINE 1311 "Graphics/X11/Xlib/Extras.hsc" #-}
    (\hsc_ptr -> pokeByteOff hsc_ptr 0) p $ ev_event_type    ev
{-# LINE 1312 "Graphics/X11/Xlib/Extras.hsc" #-}
    (\hsc_ptr -> pokeByteOff hsc_ptr 8) p $ ev_serial        ev
{-# LINE 1313 "Graphics/X11/Xlib/Extras.hsc" #-}
    (\hsc_ptr -> pokeByteOff hsc_ptr 16) p $ ev_send_event    ev
{-# LINE 1314 "Graphics/X11/Xlib/Extras.hsc" #-}
    (\hsc_ptr -> pokeByteOff hsc_ptr 24) p $ d
{-# LINE 1315 "Graphics/X11/Xlib/Extras.hsc" #-}
    (\hsc_ptr -> pokeByteOff hsc_ptr 32) p $ ev_window        ev
{-# LINE 1316 "Graphics/X11/Xlib/Extras.hsc" #-}
    (\hsc_ptr -> pokeByteOff hsc_ptr 40) p $ ev_request       ev
{-# LINE 1317 "Graphics/X11/Xlib/Extras.hsc" #-}
    (\hsc_ptr -> pokeByteOff hsc_ptr 44) p $ ev_first_keycode ev
{-# LINE 1318 "Graphics/X11/Xlib/Extras.hsc" #-}
    (\hsc_ptr -> pokeByteOff hsc_ptr 48) p $ ev_count         ev
{-# LINE 1319 "Graphics/X11/Xlib/Extras.hsc" #-}
    _ <- xRefreshKeyboardMapping p
    return ()
refreshKeyboardMapping Event
_ = () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

foreign import ccall unsafe "XlibExtras.h XRefreshKeyboardMapping"
    xRefreshKeyboardMapping :: Ptr () -> IO CInt

-- Properties

anyPropertyType :: Atom
anyPropertyType :: Window
anyPropertyType = Window
0
{-# LINE 1330 "Graphics/X11/Xlib/Extras.hsc" #-}

foreign import ccall unsafe "XlibExtras.h XChangeProperty"
    xChangeProperty :: Display -> Window -> Atom -> Atom -> CInt -> CInt -> Ptr CUChar -> CInt -> IO Status

foreign import ccall unsafe "XlibExtras.h XDeleteProperty"
    xDeleteProperty :: Display -> Window -> Atom -> IO Status

foreign import ccall unsafe "XlibExtras.h XGetWindowProperty"
    xGetWindowProperty :: Display -> Window -> Atom -> CLong -> CLong -> Bool -> Atom -> Ptr Atom -> Ptr CInt -> Ptr CULong -> Ptr CULong -> Ptr (Ptr CUChar) -> IO Status

rawGetWindowProperty :: Storable a => Int -> Display -> Atom -> Window -> IO (Maybe [a])
rawGetWindowProperty :: Int -> Display -> Window -> Window -> IO (Maybe [a])
rawGetWindowProperty Int
bits Display
d Window
atom Window
w =
    (Ptr Window -> IO (Maybe [a])) -> IO (Maybe [a])
forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca ((Ptr Window -> IO (Maybe [a])) -> IO (Maybe [a]))
-> (Ptr Window -> IO (Maybe [a])) -> IO (Maybe [a])
forall a b. (a -> b) -> a -> b
$ \Ptr Window
actual_type_return ->
    (Ptr CInt -> IO (Maybe [a])) -> IO (Maybe [a])
forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca ((Ptr CInt -> IO (Maybe [a])) -> IO (Maybe [a]))
-> (Ptr CInt -> IO (Maybe [a])) -> IO (Maybe [a])
forall a b. (a -> b) -> a -> b
$ \Ptr CInt
actual_format_return ->
    (Ptr CULong -> IO (Maybe [a])) -> IO (Maybe [a])
forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca ((Ptr CULong -> IO (Maybe [a])) -> IO (Maybe [a]))
-> (Ptr CULong -> IO (Maybe [a])) -> IO (Maybe [a])
forall a b. (a -> b) -> a -> b
$ \Ptr CULong
nitems_return ->
    (Ptr CULong -> IO (Maybe [a])) -> IO (Maybe [a])
forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca ((Ptr CULong -> IO (Maybe [a])) -> IO (Maybe [a]))
-> (Ptr CULong -> IO (Maybe [a])) -> IO (Maybe [a])
forall a b. (a -> b) -> a -> b
$ \Ptr CULong
bytes_after_return ->
    (Ptr (Ptr CUChar) -> IO (Maybe [a])) -> IO (Maybe [a])
forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca ((Ptr (Ptr CUChar) -> IO (Maybe [a])) -> IO (Maybe [a]))
-> (Ptr (Ptr CUChar) -> IO (Maybe [a])) -> IO (Maybe [a])
forall a b. (a -> b) -> a -> b
$ \Ptr (Ptr CUChar)
prop_return -> do
        CInt
ret <- Display
-> Window
-> Window
-> CLong
-> CLong
-> Bool
-> Window
-> Ptr Window
-> Ptr CInt
-> Ptr CULong
-> Ptr CULong
-> Ptr (Ptr CUChar)
-> IO CInt
xGetWindowProperty Display
d Window
w Window
atom CLong
0 CLong
0xFFFFFFFF Bool
False Window
anyPropertyType
                           Ptr Window
actual_type_return
                           Ptr CInt
actual_format_return
                           Ptr CULong
nitems_return
                           Ptr CULong
bytes_after_return
                           Ptr (Ptr CUChar)
prop_return

        if CInt
ret CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0
            then Maybe [a] -> IO (Maybe [a])
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe [a]
forall a. Maybe a
Nothing
            else do
                Ptr CUChar
prop_ptr      <- Ptr (Ptr CUChar) -> IO (Ptr CUChar)
forall a. Storable a => Ptr a -> IO a
peek Ptr (Ptr CUChar)
prop_return
                Int
actual_format <- CInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (CInt -> Int) -> IO CInt -> IO Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
`fmap` Ptr CInt -> IO CInt
forall a. Storable a => Ptr a -> IO a
peek Ptr CInt
actual_format_return
                Int
nitems        <- CULong -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (CULong -> Int) -> IO CULong -> IO Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
`fmap` Ptr CULong -> IO CULong
forall a. Storable a => Ptr a -> IO a
peek Ptr CULong
nitems_return
                Ptr CUChar -> Int -> Int -> IO (Maybe [a])
forall a a. Storable a => Ptr a -> Int -> Int -> IO (Maybe [a])
getprop Ptr CUChar
prop_ptr Int
nitems Int
actual_format
  where
    getprop :: Ptr a -> Int -> Int -> IO (Maybe [a])
getprop Ptr a
prop_ptr Int
nitems Int
actual_format
        | Int
actual_format Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0    = Maybe [a] -> IO (Maybe [a])
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe [a]
forall a. Maybe a
Nothing -- Property not found
        | Int
actual_format Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
/= Int
bits = Ptr a -> IO CInt
forall a. Ptr a -> IO CInt
xFree Ptr a
prop_ptr IO CInt -> IO (Maybe [a]) -> IO (Maybe [a])
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Maybe [a] -> IO (Maybe [a])
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe [a]
forall a. Maybe a
Nothing
        | Bool
otherwise = do
            [a]
retval <- Int -> Ptr a -> IO [a]
forall a. Storable a => Int -> Ptr a -> IO [a]
peekArray Int
nitems (Ptr a -> Ptr a
forall a b. Ptr a -> Ptr b
castPtr Ptr a
prop_ptr)
            CInt
_ <- Ptr a -> IO CInt
forall a. Ptr a -> IO CInt
xFree Ptr a
prop_ptr
            Maybe [a] -> IO (Maybe [a])
forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe [a] -> IO (Maybe [a])) -> Maybe [a] -> IO (Maybe [a])
forall a b. (a -> b) -> a -> b
$ [a] -> Maybe [a]
forall a. a -> Maybe a
Just [a]
retval

getWindowProperty8 :: Display -> Atom -> Window -> IO (Maybe [CChar])
getWindowProperty8 :: Display -> Window -> Window -> IO (Maybe [CChar])
getWindowProperty8 = Int -> Display -> Window -> Window -> IO (Maybe [CChar])
forall a.
Storable a =>
Int -> Display -> Window -> Window -> IO (Maybe [a])
rawGetWindowProperty Int
8

getWindowProperty16 :: Display -> Atom -> Window -> IO (Maybe [CShort])
getWindowProperty16 :: Display -> Window -> Window -> IO (Maybe [CShort])
getWindowProperty16 = Int -> Display -> Window -> Window -> IO (Maybe [CShort])
forall a.
Storable a =>
Int -> Display -> Window -> Window -> IO (Maybe [a])
rawGetWindowProperty Int
16

getWindowProperty32 :: Display -> Atom -> Window -> IO (Maybe [CLong])
getWindowProperty32 :: Display -> Window -> Window -> IO (Maybe [CLong])
getWindowProperty32 = Int -> Display -> Window -> Window -> IO (Maybe [CLong])
forall a.
Storable a =>
Int -> Display -> Window -> Window -> IO (Maybe [a])
rawGetWindowProperty Int
32

-- this assumes bytes are 8 bits.  I hope X isn't more portable than that :(

changeProperty8 :: Display -> Window -> Atom -> Atom -> CInt -> [CChar] -> IO ()
changeProperty8 :: Display -> Window -> Window -> Window -> CInt -> [CChar] -> IO ()
changeProperty8 Display
dpy Window
w Window
prop Window
typ CInt
mode [CChar]
dat =
    [CChar] -> (Int -> CString -> IO ()) -> IO ()
forall a b. Storable a => [a] -> (Int -> Ptr a -> IO b) -> IO b
withArrayLen [CChar]
dat ((Int -> CString -> IO ()) -> IO ())
-> (Int -> CString -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ Int
len CString
ptr -> do
        CInt
_ <- Display
-> Window
-> Window
-> Window
-> CInt
-> CInt
-> Ptr CUChar
-> CInt
-> IO CInt
xChangeProperty Display
dpy Window
w Window
prop Window
typ CInt
8 CInt
mode (CString -> Ptr CUChar
forall a b. Ptr a -> Ptr b
castPtr CString
ptr) (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
len)
        () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

changeProperty16 :: Display -> Window -> Atom -> Atom -> CInt -> [CShort] -> IO ()
changeProperty16 :: Display -> Window -> Window -> Window -> CInt -> [CShort] -> IO ()
changeProperty16 Display
dpy Window
w Window
prop Window
typ CInt
mode [CShort]
dat =
    [CShort] -> (Int -> Ptr CShort -> IO ()) -> IO ()
forall a b. Storable a => [a] -> (Int -> Ptr a -> IO b) -> IO b
withArrayLen [CShort]
dat ((Int -> Ptr CShort -> IO ()) -> IO ())
-> (Int -> Ptr CShort -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ Int
len Ptr CShort
ptr -> do
        CInt
_ <- Display
-> Window
-> Window
-> Window
-> CInt
-> CInt
-> Ptr CUChar
-> CInt
-> IO CInt
xChangeProperty Display
dpy Window
w Window
prop Window
typ CInt
16 CInt
mode (Ptr CShort -> Ptr CUChar
forall a b. Ptr a -> Ptr b
castPtr Ptr CShort
ptr) (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
len)
        () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

changeProperty32 :: Display -> Window -> Atom -> Atom -> CInt -> [CLong] -> IO ()
changeProperty32 :: Display -> Window -> Window -> Window -> CInt -> [CLong] -> IO ()
changeProperty32 Display
dpy Window
w Window
prop Window
typ CInt
mode [CLong]
dat =
    [CLong] -> (Int -> Ptr CLong -> IO ()) -> IO ()
forall a b. Storable a => [a] -> (Int -> Ptr a -> IO b) -> IO b
withArrayLen [CLong]
dat ((Int -> Ptr CLong -> IO ()) -> IO ())
-> (Int -> Ptr CLong -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ Int
len Ptr CLong
ptr -> do
        CInt
_ <- Display
-> Window
-> Window
-> Window
-> CInt
-> CInt
-> Ptr CUChar
-> CInt
-> IO CInt
xChangeProperty Display
dpy Window
w Window
prop Window
typ CInt
32 CInt
mode (Ptr CLong -> Ptr CUChar
forall a b. Ptr a -> Ptr b
castPtr Ptr CLong
ptr) (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
len)
        () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

propModeReplace, propModePrepend, propModeAppend :: CInt
propModeReplace :: CInt
propModeReplace = CInt
0
{-# LINE 1401 "Graphics/X11/Xlib/Extras.hsc" #-}
propModePrepend = 1
{-# LINE 1402 "Graphics/X11/Xlib/Extras.hsc" #-}
propModeAppend = 2
{-# LINE 1403 "Graphics/X11/Xlib/Extras.hsc" #-}

deleteProperty :: Display -> Window -> Atom -> IO ()
deleteProperty :: Display -> Window -> Window -> IO ()
deleteProperty Display
dpy Window
w Window
prop = do
    CInt
_ <- Display -> Window -> Window -> IO CInt
xDeleteProperty Display
dpy Window
w Window
prop
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

-- Windows

foreign import ccall unsafe "XlibExtras.h XUnmapWindow"
    xUnmapWindow :: Display -> Window -> IO CInt

unmapWindow :: Display -> Window -> IO ()
unmapWindow :: Display -> Window -> IO ()
unmapWindow Display
d Window
w = Display -> Window -> IO CInt
xUnmapWindow Display
d Window
w IO CInt -> IO () -> IO ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

------------------------------------------------------------------------
-- Size hints

data SizeHints = SizeHints
                   { SizeHints -> Maybe (EventType, EventType)
sh_min_size     :: Maybe (Dimension, Dimension)
                   , SizeHints -> Maybe (EventType, EventType)
sh_max_size     :: Maybe (Dimension, Dimension)
                   , SizeHints -> Maybe (EventType, EventType)
sh_resize_inc   :: Maybe (Dimension, Dimension)
                   , SizeHints -> Maybe ((EventType, EventType), (EventType, EventType))
sh_aspect       :: Maybe ((Dimension, Dimension), (Dimension, Dimension))
                   , SizeHints -> Maybe (EventType, EventType)
sh_base_size    :: Maybe (Dimension, Dimension)
                   , SizeHints -> Maybe CInt
sh_win_gravity  :: Maybe (BitGravity)
                   }

pMinSizeBit, pMaxSizeBit, pResizeIncBit, pAspectBit, pBaseSizeBit, pWinGravityBit :: Int
pMinSizeBit :: Int
pMinSizeBit    = Int
4
pMaxSizeBit :: Int
pMaxSizeBit    = Int
5
pResizeIncBit :: Int
pResizeIncBit  = Int
6
pAspectBit :: Int
pAspectBit     = Int
7
pBaseSizeBit :: Int
pBaseSizeBit   = Int
8
pWinGravityBit :: Int
pWinGravityBit = Int
9

instance Storable SizeHints where
    alignment :: SizeHints -> Int
alignment SizeHints
_ = CInt -> Int
forall a. Storable a => a -> Int
alignment (CInt
forall a. HasCallStack => a
undefined :: CInt)
    sizeOf :: SizeHints -> Int
sizeOf SizeHints
_ = (Int
80)
{-# LINE 1440 "Graphics/X11/Xlib/Extras.hsc" #-}

    poke :: Ptr SizeHints -> SizeHints -> IO ()
poke Ptr SizeHints
p SizeHints
sh = do
      let whenSet :: (SizeHints -> Maybe a) -> (a -> m ()) -> m ()
whenSet SizeHints -> Maybe a
f a -> m ()
x = m () -> (a -> m ()) -> Maybe a -> m ()
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (() -> m ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()) a -> m ()
x (SizeHints -> Maybe a
f SizeHints
sh)
      let pokeFlag :: Int -> IO ()
pokeFlag Int
b = do CLong
flag <- (\Ptr SizeHints
hsc_ptr -> Ptr SizeHints -> Int -> IO CLong
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr SizeHints
hsc_ptr Int
0) Ptr SizeHints
p :: IO CLong
{-# LINE 1444 "Graphics/X11/Xlib/Extras.hsc" #-}
                          (\Ptr SizeHints
hsc_ptr -> Ptr SizeHints -> Int -> CLong -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr SizeHints
hsc_ptr Int
0) Ptr SizeHints
p (CLong -> Int -> CLong
forall a. Bits a => a -> Int -> a
setBit CLong
flag Int
b)
{-# LINE 1445 "Graphics/X11/Xlib/Extras.hsc" #-}
      (\hsc_ptr -> pokeByteOff hsc_ptr 0) p (0 :: CLong)
{-# LINE 1446 "Graphics/X11/Xlib/Extras.hsc" #-}
      whenSet sh_min_size $ \(w, h) -> do
        pokeFlag pMinSizeBit
        (\hsc_ptr -> pokeByteOff hsc_ptr 24) p w
{-# LINE 1449 "Graphics/X11/Xlib/Extras.hsc" #-}
        (\hsc_ptr -> pokeByteOff hsc_ptr 28) p h
{-# LINE 1450 "Graphics/X11/Xlib/Extras.hsc" #-}
      whenSet sh_max_size $ \(w, h) -> do
        pokeFlag pMaxSizeBit
        (\hsc_ptr -> pokeByteOff hsc_ptr 32) p w
{-# LINE 1453 "Graphics/X11/Xlib/Extras.hsc" #-}
        (\hsc_ptr -> pokeByteOff hsc_ptr 36) p h
{-# LINE 1454 "Graphics/X11/Xlib/Extras.hsc" #-}
      whenSet sh_resize_inc $ \(w, h) -> do
        pokeFlag pResizeIncBit
        (\hsc_ptr -> pokeByteOff hsc_ptr 40) p w
{-# LINE 1457 "Graphics/X11/Xlib/Extras.hsc" #-}
        (\hsc_ptr -> pokeByteOff hsc_ptr 44) p h
{-# LINE 1458 "Graphics/X11/Xlib/Extras.hsc" #-}
      whenSet sh_aspect $ \((minx, miny), (maxx, maxy)) -> do
        pokeFlag pAspectBit
        (\hsc_ptr -> pokeByteOff hsc_ptr 48) p minx
{-# LINE 1461 "Graphics/X11/Xlib/Extras.hsc" #-}
        (\hsc_ptr -> pokeByteOff hsc_ptr 52) p miny
{-# LINE 1462 "Graphics/X11/Xlib/Extras.hsc" #-}
        (\hsc_ptr -> pokeByteOff hsc_ptr 56) p maxx
{-# LINE 1463 "Graphics/X11/Xlib/Extras.hsc" #-}
        (\hsc_ptr -> pokeByteOff hsc_ptr 60) p maxy
{-# LINE 1464 "Graphics/X11/Xlib/Extras.hsc" #-}
      whenSet sh_base_size $ \(w, h) -> do
        pokeFlag pBaseSizeBit
        (\hsc_ptr -> pokeByteOff hsc_ptr 64) p w
{-# LINE 1467 "Graphics/X11/Xlib/Extras.hsc" #-}
        (\hsc_ptr -> pokeByteOff hsc_ptr 68) p h
{-# LINE 1468 "Graphics/X11/Xlib/Extras.hsc" #-}
      whenSet sh_win_gravity $ \g -> do
        pokeFlag pWinGravityBit
        (\hsc_ptr -> pokeByteOff hsc_ptr 72) p g
{-# LINE 1471 "Graphics/X11/Xlib/Extras.hsc" #-}

    peek :: Ptr SizeHints -> IO SizeHints
peek Ptr SizeHints
p = do
      CLong
flags <- (\Ptr SizeHints
hsc_ptr -> Ptr SizeHints -> Int -> IO CLong
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr SizeHints
hsc_ptr Int
0) Ptr SizeHints
p :: IO CLong
{-# LINE 1474 "Graphics/X11/Xlib/Extras.hsc" #-}
      let whenBit n x = if testBit flags n then liftM Just x else return Nothing
      (Maybe (EventType, EventType)
 -> Maybe (EventType, EventType)
 -> Maybe (EventType, EventType)
 -> Maybe ((EventType, EventType), (EventType, EventType))
 -> Maybe (EventType, EventType)
 -> Maybe CInt
 -> SizeHints)
-> IO
     (Maybe (EventType, EventType)
      -> Maybe (EventType, EventType)
      -> Maybe (EventType, EventType)
      -> Maybe ((EventType, EventType), (EventType, EventType))
      -> Maybe (EventType, EventType)
      -> Maybe CInt
      -> SizeHints)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe (EventType, EventType)
-> Maybe (EventType, EventType)
-> Maybe (EventType, EventType)
-> Maybe ((EventType, EventType), (EventType, EventType))
-> Maybe (EventType, EventType)
-> Maybe CInt
-> SizeHints
SizeHints
         IO
  (Maybe (EventType, EventType)
   -> Maybe (EventType, EventType)
   -> Maybe (EventType, EventType)
   -> Maybe ((EventType, EventType), (EventType, EventType))
   -> Maybe (EventType, EventType)
   -> Maybe CInt
   -> SizeHints)
-> IO (Maybe (EventType, EventType))
-> IO
     (Maybe (EventType, EventType)
      -> Maybe (EventType, EventType)
      -> Maybe ((EventType, EventType), (EventType, EventType))
      -> Maybe (EventType, EventType)
      -> Maybe CInt
      -> SizeHints)
forall (m :: * -> *) a b. Monad m => m (a -> b) -> m a -> m b
`ap` Int
-> IO (EventType, EventType) -> IO (Maybe (EventType, EventType))
forall (m :: * -> *) a. Monad m => Int -> m a -> m (Maybe a)
whenBit Int
pMinSizeBit    (do (EventType -> EventType -> (EventType, EventType))
-> IO EventType -> IO EventType -> IO (EventType, EventType)
forall (m :: * -> *) a1 a2 r.
Monad m =>
(a1 -> a2 -> r) -> m a1 -> m a2 -> m r
liftM2 (,) ((\Ptr SizeHints
hsc_ptr -> Ptr SizeHints -> Int -> IO EventType
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr SizeHints
hsc_ptr Int
24) Ptr SizeHints
p)
{-# LINE 1477 "Graphics/X11/Xlib/Extras.hsc" #-}
                                                    ((\Ptr SizeHints
hsc_ptr -> Ptr SizeHints -> Int -> IO EventType
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr SizeHints
hsc_ptr Int
28) Ptr SizeHints
p))
{-# LINE 1478 "Graphics/X11/Xlib/Extras.hsc" #-}
         IO
  (Maybe (EventType, EventType)
   -> Maybe (EventType, EventType)
   -> Maybe ((EventType, EventType), (EventType, EventType))
   -> Maybe (EventType, EventType)
   -> Maybe CInt
   -> SizeHints)
-> IO (Maybe (EventType, EventType))
-> IO
     (Maybe (EventType, EventType)
      -> Maybe ((EventType, EventType), (EventType, EventType))
      -> Maybe (EventType, EventType)
      -> Maybe CInt
      -> SizeHints)
forall (m :: * -> *) a b. Monad m => m (a -> b) -> m a -> m b
`ap` Int
-> IO (EventType, EventType) -> IO (Maybe (EventType, EventType))
forall (m :: * -> *) a. Monad m => Int -> m a -> m (Maybe a)
whenBit Int
pMaxSizeBit    (do (EventType -> EventType -> (EventType, EventType))
-> IO EventType -> IO EventType -> IO (EventType, EventType)
forall (m :: * -> *) a1 a2 r.
Monad m =>
(a1 -> a2 -> r) -> m a1 -> m a2 -> m r
liftM2 (,) ((\Ptr SizeHints
hsc_ptr -> Ptr SizeHints -> Int -> IO EventType
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr SizeHints
hsc_ptr Int
32) Ptr SizeHints
p)
{-# LINE 1479 "Graphics/X11/Xlib/Extras.hsc" #-}
                                                    ((\Ptr SizeHints
hsc_ptr -> Ptr SizeHints -> Int -> IO EventType
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr SizeHints
hsc_ptr Int
36) Ptr SizeHints
p))
{-# LINE 1480 "Graphics/X11/Xlib/Extras.hsc" #-}
         IO
  (Maybe (EventType, EventType)
   -> Maybe ((EventType, EventType), (EventType, EventType))
   -> Maybe (EventType, EventType)
   -> Maybe CInt
   -> SizeHints)
-> IO (Maybe (EventType, EventType))
-> IO
     (Maybe ((EventType, EventType), (EventType, EventType))
      -> Maybe (EventType, EventType) -> Maybe CInt -> SizeHints)
forall (m :: * -> *) a b. Monad m => m (a -> b) -> m a -> m b
`ap` Int
-> IO (EventType, EventType) -> IO (Maybe (EventType, EventType))
forall (m :: * -> *) a. Monad m => Int -> m a -> m (Maybe a)
whenBit Int
pResizeIncBit  (do (EventType -> EventType -> (EventType, EventType))
-> IO EventType -> IO EventType -> IO (EventType, EventType)
forall (m :: * -> *) a1 a2 r.
Monad m =>
(a1 -> a2 -> r) -> m a1 -> m a2 -> m r
liftM2 (,) ((\Ptr SizeHints
hsc_ptr -> Ptr SizeHints -> Int -> IO EventType
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr SizeHints
hsc_ptr Int
40) Ptr SizeHints
p)
{-# LINE 1481 "Graphics/X11/Xlib/Extras.hsc" #-}
                                                    ((\Ptr SizeHints
hsc_ptr -> Ptr SizeHints -> Int -> IO EventType
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr SizeHints
hsc_ptr Int
44) Ptr SizeHints
p))
{-# LINE 1482 "Graphics/X11/Xlib/Extras.hsc" #-}
         IO
  (Maybe ((EventType, EventType), (EventType, EventType))
   -> Maybe (EventType, EventType) -> Maybe CInt -> SizeHints)
-> IO (Maybe ((EventType, EventType), (EventType, EventType)))
-> IO (Maybe (EventType, EventType) -> Maybe CInt -> SizeHints)
forall (m :: * -> *) a b. Monad m => m (a -> b) -> m a -> m b
`ap` Int
-> IO ((EventType, EventType), (EventType, EventType))
-> IO (Maybe ((EventType, EventType), (EventType, EventType)))
forall (m :: * -> *) a. Monad m => Int -> m a -> m (Maybe a)
whenBit Int
pAspectBit     (do EventType
minx <- (\Ptr SizeHints
hsc_ptr -> Ptr SizeHints -> Int -> IO EventType
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr SizeHints
hsc_ptr Int
48) Ptr SizeHints
p
{-# LINE 1483 "Graphics/X11/Xlib/Extras.hsc" #-}
                                         EventType
miny <- (\Ptr SizeHints
hsc_ptr -> Ptr SizeHints -> Int -> IO EventType
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr SizeHints
hsc_ptr Int
52) Ptr SizeHints
p
{-# LINE 1484 "Graphics/X11/Xlib/Extras.hsc" #-}
                                         EventType
maxx <- (\Ptr SizeHints
hsc_ptr -> Ptr SizeHints -> Int -> IO EventType
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr SizeHints
hsc_ptr Int
56) Ptr SizeHints
p
{-# LINE 1485 "Graphics/X11/Xlib/Extras.hsc" #-}
                                         EventType
maxy <- (\Ptr SizeHints
hsc_ptr -> Ptr SizeHints -> Int -> IO EventType
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr SizeHints
hsc_ptr Int
60) Ptr SizeHints
p
{-# LINE 1486 "Graphics/X11/Xlib/Extras.hsc" #-}
                                         ((EventType, EventType), (EventType, EventType))
-> IO ((EventType, EventType), (EventType, EventType))
forall (m :: * -> *) a. Monad m => a -> m a
return ((EventType
minx, EventType
miny), (EventType
maxx, EventType
maxy)))
         IO (Maybe (EventType, EventType) -> Maybe CInt -> SizeHints)
-> IO (Maybe (EventType, EventType))
-> IO (Maybe CInt -> SizeHints)
forall (m :: * -> *) a b. Monad m => m (a -> b) -> m a -> m b
`ap` Int
-> IO (EventType, EventType) -> IO (Maybe (EventType, EventType))
forall (m :: * -> *) a. Monad m => Int -> m a -> m (Maybe a)
whenBit Int
pBaseSizeBit   (do (EventType -> EventType -> (EventType, EventType))
-> IO EventType -> IO EventType -> IO (EventType, EventType)
forall (m :: * -> *) a1 a2 r.
Monad m =>
(a1 -> a2 -> r) -> m a1 -> m a2 -> m r
liftM2 (,) ((\Ptr SizeHints
hsc_ptr -> Ptr SizeHints -> Int -> IO EventType
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr SizeHints
hsc_ptr Int
64) Ptr SizeHints
p)
{-# LINE 1488 "Graphics/X11/Xlib/Extras.hsc" #-}
                                                    ((\Ptr SizeHints
hsc_ptr -> Ptr SizeHints -> Int -> IO EventType
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr SizeHints
hsc_ptr Int
68) Ptr SizeHints
p))
{-# LINE 1489 "Graphics/X11/Xlib/Extras.hsc" #-}
         IO (Maybe CInt -> SizeHints) -> IO (Maybe CInt) -> IO SizeHints
forall (m :: * -> *) a b. Monad m => m (a -> b) -> m a -> m b
`ap` Int -> IO CInt -> IO (Maybe CInt)
forall (m :: * -> *) a. Monad m => Int -> m a -> m (Maybe a)
whenBit Int
pWinGravityBit ((\Ptr SizeHints
hsc_ptr -> Ptr SizeHints -> Int -> IO CInt
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr SizeHints
hsc_ptr Int
72) Ptr SizeHints
p)
{-# LINE 1490 "Graphics/X11/Xlib/Extras.hsc" #-}


foreign import ccall unsafe "XlibExtras.h XGetWMNormalHints"
    xGetWMNormalHints :: Display -> Window -> Ptr SizeHints -> Ptr CLong -> IO Status

getWMNormalHints :: Display -> Window -> IO SizeHints
getWMNormalHints :: Display -> Window -> IO SizeHints
getWMNormalHints Display
d Window
w
    = (Ptr SizeHints -> IO SizeHints) -> IO SizeHints
forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca ((Ptr SizeHints -> IO SizeHints) -> IO SizeHints)
-> (Ptr SizeHints -> IO SizeHints) -> IO SizeHints
forall a b. (a -> b) -> a -> b
$ \Ptr SizeHints
sh -> do
        (Ptr CLong -> IO SizeHints) -> IO SizeHints
forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca ((Ptr CLong -> IO SizeHints) -> IO SizeHints)
-> (Ptr CLong -> IO SizeHints) -> IO SizeHints
forall a b. (a -> b) -> a -> b
$ \Ptr CLong
supplied_return -> do
          -- what's the purpose of supplied_return?
          CInt
status <- Display -> Window -> Ptr SizeHints -> Ptr CLong -> IO CInt
xGetWMNormalHints Display
d Window
w Ptr SizeHints
sh Ptr CLong
supplied_return
          case CInt
status of
            CInt
0 -> SizeHints -> IO SizeHints
forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe (EventType, EventType)
-> Maybe (EventType, EventType)
-> Maybe (EventType, EventType)
-> Maybe ((EventType, EventType), (EventType, EventType))
-> Maybe (EventType, EventType)
-> Maybe CInt
-> SizeHints
SizeHints Maybe (EventType, EventType)
forall a. Maybe a
Nothing Maybe (EventType, EventType)
forall a. Maybe a
Nothing Maybe (EventType, EventType)
forall a. Maybe a
Nothing Maybe ((EventType, EventType), (EventType, EventType))
forall a. Maybe a
Nothing Maybe (EventType, EventType)
forall a. Maybe a
Nothing Maybe CInt
forall a. Maybe a
Nothing)
            CInt
_ -> Ptr SizeHints -> IO SizeHints
forall a. Storable a => Ptr a -> IO a
peek Ptr SizeHints
sh


data ClassHint = ClassHint
                        { ClassHint -> String
resName  :: String
                        , ClassHint -> String
resClass :: String
                        }

getClassHint :: Display -> Window -> IO ClassHint
getClassHint :: Display -> Window -> IO ClassHint
getClassHint Display
d Window
w =  Int -> (Ptr ClassHint -> IO ClassHint) -> IO ClassHint
forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes ((Int
16)) ((Ptr ClassHint -> IO ClassHint) -> IO ClassHint)
-> (Ptr ClassHint -> IO ClassHint) -> IO ClassHint
forall a b. (a -> b) -> a -> b
$ \ Ptr ClassHint
p -> do
{-# LINE 1513 "Graphics/X11/Xlib/Extras.hsc" #-}
    s <- xGetClassHint d w p
    if s /= 0 -- returns a nonzero status on success
        then do
            res_name_p <- (\hsc_ptr -> peekByteOff hsc_ptr 0) p
{-# LINE 1517 "Graphics/X11/Xlib/Extras.hsc" #-}
            res_class_p <- (\hsc_ptr -> peekByteOff hsc_ptr 8) p
{-# LINE 1518 "Graphics/X11/Xlib/Extras.hsc" #-}
            res <- liftM2 ClassHint (peekCString res_name_p) (peekCString res_class_p)
            _ <- xFree res_name_p
            _ <- xFree res_class_p
            return res
        else return $ ClassHint "" ""

foreign import ccall unsafe "XlibExtras.h XGetClassHint"
    xGetClassHint :: Display -> Window -> Ptr ClassHint -> IO Status

-- | Set the @WM_CLASS@ property for the given window.
setClassHint :: Display -> Window -> ClassHint -> IO ()
setClassHint :: Display -> Window -> ClassHint -> IO ()
setClassHint Display
dpy Window
win (ClassHint String
name String
cl) =
    Int -> (Ptr ClassHint -> IO ()) -> IO ()
forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes ((Int
16)) ((Ptr ClassHint -> IO ()) -> IO ())
-> (Ptr ClassHint -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr ClassHint
ptr -> do
{-# LINE 1531 "Graphics/X11/Xlib/Extras.hsc" #-}
        String -> (CString -> IO ()) -> IO ()
forall a. String -> (CString -> IO a) -> IO a
withCString String
name ((CString -> IO ()) -> IO ()) -> (CString -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \CString
c_name -> String -> (CString -> IO ()) -> IO ()
forall a. String -> (CString -> IO a) -> IO a
withCString String
cl ((CString -> IO ()) -> IO ()) -> (CString -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \CString
c_cl -> do
            (\Ptr ClassHint
hsc_ptr -> Ptr ClassHint -> Int -> CString -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr ClassHint
hsc_ptr Int
0) Ptr ClassHint
ptr CString
c_name
{-# LINE 1533 "Graphics/X11/Xlib/Extras.hsc" #-}
            (\Ptr ClassHint
hsc_ptr -> Ptr ClassHint -> Int -> CString -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr ClassHint
hsc_ptr Int
8) Ptr ClassHint
ptr CString
c_cl
{-# LINE 1534 "Graphics/X11/Xlib/Extras.hsc" #-}
            Display -> Window -> Ptr ClassHint -> IO ()
xSetClassHint Display
dpy Window
win Ptr ClassHint
ptr

foreign import ccall unsafe "XlibExtras.h XSetClassHint"
    xSetClassHint :: Display -> Window -> Ptr ClassHint -> IO ()

------------------------------------------------------------------------
-- WM Hints

-- These are the documented values for a window's "WM State", set, for example,
-- in wmh_initial_state, below. Note, you may need to play games with
-- fromIntegral and/or fromEnum.
withdrawnState,normalState, iconicState :: Int
withdrawnState :: Int
withdrawnState = Int
0
{-# LINE 1547 "Graphics/X11/Xlib/Extras.hsc" #-}
normalState    = 1
{-# LINE 1548 "Graphics/X11/Xlib/Extras.hsc" #-}
iconicState    = 3
{-# LINE 1549 "Graphics/X11/Xlib/Extras.hsc" #-}

-- The following values are the documented bit positions on XWMHints's flags field.
-- Use testBit, setBit, and clearBit to manipulate the field.
inputHintBit,stateHintBit,iconPixmapHintBit,iconWindowHintBit,iconPositionHintBit,iconMaskHintBit,windowGroupHintBit,urgencyHintBit :: Int
inputHintBit :: Int
inputHintBit        = Int
0
stateHintBit :: Int
stateHintBit        = Int
1
iconPixmapHintBit :: Int
iconPixmapHintBit   = Int
2
iconWindowHintBit :: Int
iconWindowHintBit   = Int
3
iconPositionHintBit :: Int
iconPositionHintBit = Int
4
iconMaskHintBit :: Int
iconMaskHintBit     = Int
5
windowGroupHintBit :: Int
windowGroupHintBit  = Int
6
urgencyHintBit :: Int
urgencyHintBit      = Int
8

-- The following bitmask tests for the presence of all bits except for the
-- urgencyHintBit.
allHintsBitmask :: CLong
allHintsBitmask :: CLong
allHintsBitmask    = CLong
127
{-# LINE 1566 "Graphics/X11/Xlib/Extras.hsc" #-}

data WMHints = WMHints
                 { WMHints -> CLong
wmh_flags         :: CLong
                 , WMHints -> Bool
wmh_input         :: Bool
                 , WMHints -> CInt
wmh_initial_state :: CInt
                 , WMHints -> Window
wmh_icon_pixmap   :: Pixmap
                 , WMHints -> Window
wmh_icon_window   :: Window
                 , WMHints -> CInt
wmh_icon_x        :: CInt
                 , WMHints -> CInt
wmh_icon_y        :: CInt
                 , WMHints -> Window
wmh_icon_mask     :: Pixmap
                 , WMHints -> Window
wmh_window_group  :: XID
                 }

instance Storable WMHints where
    -- should align to the alignment of the largest type
    alignment :: WMHints -> Int
alignment WMHints
_ = CLong -> Int
forall a. Storable a => a -> Int
alignment (CLong
forall a. HasCallStack => a
undefined :: CLong)
    sizeOf :: WMHints -> Int
sizeOf WMHints
_ = (Int
56)
{-# LINE 1583 "Graphics/X11/Xlib/Extras.hsc" #-}

    peek :: Ptr WMHints -> IO WMHints
peek Ptr WMHints
p = (CLong
 -> Bool
 -> CInt
 -> Window
 -> Window
 -> CInt
 -> CInt
 -> Window
 -> Window
 -> WMHints)
-> IO
     (CLong
      -> Bool
      -> CInt
      -> Window
      -> Window
      -> CInt
      -> CInt
      -> Window
      -> Window
      -> WMHints)
forall (m :: * -> *) a. Monad m => a -> m a
return CLong
-> Bool
-> CInt
-> Window
-> Window
-> CInt
-> CInt
-> Window
-> Window
-> WMHints
WMHints
                IO
  (CLong
   -> Bool
   -> CInt
   -> Window
   -> Window
   -> CInt
   -> CInt
   -> Window
   -> Window
   -> WMHints)
-> IO CLong
-> IO
     (Bool
      -> CInt
      -> Window
      -> Window
      -> CInt
      -> CInt
      -> Window
      -> Window
      -> WMHints)
forall (m :: * -> *) a b. Monad m => m (a -> b) -> m a -> m b
`ap` (\Ptr WMHints
hsc_ptr -> Ptr WMHints -> Int -> IO CLong
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr WMHints
hsc_ptr Int
0)         Ptr WMHints
p
{-# LINE 1586 "Graphics/X11/Xlib/Extras.hsc" #-}
                IO
  (Bool
   -> CInt
   -> Window
   -> Window
   -> CInt
   -> CInt
   -> Window
   -> Window
   -> WMHints)
-> IO Bool
-> IO
     (CInt
      -> Window -> Window -> CInt -> CInt -> Window -> Window -> WMHints)
forall (m :: * -> *) a b. Monad m => m (a -> b) -> m a -> m b
`ap` (\Ptr WMHints
hsc_ptr -> Ptr WMHints -> Int -> IO Bool
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr WMHints
hsc_ptr Int
8)         Ptr WMHints
p
{-# LINE 1587 "Graphics/X11/Xlib/Extras.hsc" #-}
                IO
  (CInt
   -> Window -> Window -> CInt -> CInt -> Window -> Window -> WMHints)
-> IO CInt
-> IO
     (Window -> Window -> CInt -> CInt -> Window -> Window -> WMHints)
forall (m :: * -> *) a b. Monad m => m (a -> b) -> m a -> m b
`ap` (\Ptr WMHints
hsc_ptr -> Ptr WMHints -> Int -> IO CInt
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr WMHints
hsc_ptr Int
12) Ptr WMHints
p
{-# LINE 1588 "Graphics/X11/Xlib/Extras.hsc" #-}
                IO
  (Window -> Window -> CInt -> CInt -> Window -> Window -> WMHints)
-> IO Window
-> IO (Window -> CInt -> CInt -> Window -> Window -> WMHints)
forall (m :: * -> *) a b. Monad m => m (a -> b) -> m a -> m b
`ap` (\Ptr WMHints
hsc_ptr -> Ptr WMHints -> Int -> IO Window
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr WMHints
hsc_ptr Int
16)   Ptr WMHints
p
{-# LINE 1589 "Graphics/X11/Xlib/Extras.hsc" #-}
                IO (Window -> CInt -> CInt -> Window -> Window -> WMHints)
-> IO Window -> IO (CInt -> CInt -> Window -> Window -> WMHints)
forall (m :: * -> *) a b. Monad m => m (a -> b) -> m a -> m b
`ap` (\Ptr WMHints
hsc_ptr -> Ptr WMHints -> Int -> IO Window
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr WMHints
hsc_ptr Int
24)   Ptr WMHints
p
{-# LINE 1590 "Graphics/X11/Xlib/Extras.hsc" #-}
                IO (CInt -> CInt -> Window -> Window -> WMHints)
-> IO CInt -> IO (CInt -> Window -> Window -> WMHints)
forall (m :: * -> *) a b. Monad m => m (a -> b) -> m a -> m b
`ap` (\Ptr WMHints
hsc_ptr -> Ptr WMHints -> Int -> IO CInt
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr WMHints
hsc_ptr Int
32)        Ptr WMHints
p
{-# LINE 1591 "Graphics/X11/Xlib/Extras.hsc" #-}
                IO (CInt -> Window -> Window -> WMHints)
-> IO CInt -> IO (Window -> Window -> WMHints)
forall (m :: * -> *) a b. Monad m => m (a -> b) -> m a -> m b
`ap` (\Ptr WMHints
hsc_ptr -> Ptr WMHints -> Int -> IO CInt
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr WMHints
hsc_ptr Int
32)        Ptr WMHints
p
{-# LINE 1592 "Graphics/X11/Xlib/Extras.hsc" #-}
                IO (Window -> Window -> WMHints)
-> IO Window -> IO (Window -> WMHints)
forall (m :: * -> *) a b. Monad m => m (a -> b) -> m a -> m b
`ap` (\Ptr WMHints
hsc_ptr -> Ptr WMHints -> Int -> IO Window
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr WMHints
hsc_ptr Int
40)     Ptr WMHints
p
{-# LINE 1593 "Graphics/X11/Xlib/Extras.hsc" #-}
                IO (Window -> WMHints) -> IO Window -> IO WMHints
forall (m :: * -> *) a b. Monad m => m (a -> b) -> m a -> m b
`ap` (\Ptr WMHints
hsc_ptr -> Ptr WMHints -> Int -> IO Window
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr WMHints
hsc_ptr Int
48)  Ptr WMHints
p
{-# LINE 1594 "Graphics/X11/Xlib/Extras.hsc" #-}

    poke :: Ptr WMHints -> WMHints -> IO ()
poke Ptr WMHints
p WMHints
wmh = do
        (\Ptr WMHints
hsc_ptr -> Ptr WMHints -> Int -> CLong -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr WMHints
hsc_ptr Int
0)         Ptr WMHints
p (CLong -> IO ()) -> CLong -> IO ()
forall a b. (a -> b) -> a -> b
$ WMHints -> CLong
wmh_flags         WMHints
wmh
{-# LINE 1597 "Graphics/X11/Xlib/Extras.hsc" #-}
        (\Ptr WMHints
hsc_ptr -> Ptr WMHints -> Int -> Bool -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr WMHints
hsc_ptr Int
8)         Ptr WMHints
p (Bool -> IO ()) -> Bool -> IO ()
forall a b. (a -> b) -> a -> b
$ WMHints -> Bool
wmh_input         WMHints
wmh
{-# LINE 1598 "Graphics/X11/Xlib/Extras.hsc" #-}
        (\Ptr WMHints
hsc_ptr -> Ptr WMHints -> Int -> CInt -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr WMHints
hsc_ptr Int
12) Ptr WMHints
p (CInt -> IO ()) -> CInt -> IO ()
forall a b. (a -> b) -> a -> b
$ WMHints -> CInt
wmh_initial_state WMHints
wmh
{-# LINE 1599 "Graphics/X11/Xlib/Extras.hsc" #-}
        (\Ptr WMHints
hsc_ptr -> Ptr WMHints -> Int -> Window -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr WMHints
hsc_ptr Int
16)   Ptr WMHints
p (Window -> IO ()) -> Window -> IO ()
forall a b. (a -> b) -> a -> b
$ WMHints -> Window
wmh_icon_pixmap   WMHints
wmh
{-# LINE 1600 "Graphics/X11/Xlib/Extras.hsc" #-}
        (\Ptr WMHints
hsc_ptr -> Ptr WMHints -> Int -> Window -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr WMHints
hsc_ptr Int
24)   Ptr WMHints
p (Window -> IO ()) -> Window -> IO ()
forall a b. (a -> b) -> a -> b
$ WMHints -> Window
wmh_icon_window   WMHints
wmh
{-# LINE 1601 "Graphics/X11/Xlib/Extras.hsc" #-}
        (\Ptr WMHints
hsc_ptr -> Ptr WMHints -> Int -> CInt -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr WMHints
hsc_ptr Int
32)        Ptr WMHints
p (CInt -> IO ()) -> CInt -> IO ()
forall a b. (a -> b) -> a -> b
$ WMHints -> CInt
wmh_icon_x        WMHints
wmh
{-# LINE 1602 "Graphics/X11/Xlib/Extras.hsc" #-}
        (\Ptr WMHints
hsc_ptr -> Ptr WMHints -> Int -> CInt -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr WMHints
hsc_ptr Int
36)        Ptr WMHints
p (CInt -> IO ()) -> CInt -> IO ()
forall a b. (a -> b) -> a -> b
$ WMHints -> CInt
wmh_icon_y        WMHints
wmh
{-# LINE 1603 "Graphics/X11/Xlib/Extras.hsc" #-}
        (\Ptr WMHints
hsc_ptr -> Ptr WMHints -> Int -> Window -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr WMHints
hsc_ptr Int
40)     Ptr WMHints
p (Window -> IO ()) -> Window -> IO ()
forall a b. (a -> b) -> a -> b
$ WMHints -> Window
wmh_icon_mask     WMHints
wmh
{-# LINE 1604 "Graphics/X11/Xlib/Extras.hsc" #-}
        (\Ptr WMHints
hsc_ptr -> Ptr WMHints -> Int -> Window -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr WMHints
hsc_ptr Int
48)  Ptr WMHints
p (Window -> IO ()) -> Window -> IO ()
forall a b. (a -> b) -> a -> b
$ WMHints -> Window
wmh_window_group  WMHints
wmh
{-# LINE 1605 "Graphics/X11/Xlib/Extras.hsc" #-}

foreign import ccall unsafe "XlibExtras.h XGetWMHints"
    xGetWMHints :: Display -> Window -> IO (Ptr WMHints)

getWMHints :: Display -> Window -> IO WMHints
getWMHints :: Display -> Window -> IO WMHints
getWMHints Display
dpy Window
w = do
    Ptr WMHints
p <- Display -> Window -> IO (Ptr WMHints)
xGetWMHints Display
dpy Window
w
    if Ptr WMHints
p Ptr WMHints -> Ptr WMHints -> Bool
forall a. Eq a => a -> a -> Bool
== Ptr WMHints
forall b. Ptr b
nullPtr
        then WMHints -> IO WMHints
forall (m :: * -> *) a. Monad m => a -> m a
return (WMHints -> IO WMHints) -> WMHints -> IO WMHints
forall a b. (a -> b) -> a -> b
$ CLong
-> Bool
-> CInt
-> Window
-> Window
-> CInt
-> CInt
-> Window
-> Window
-> WMHints
WMHints CLong
0 Bool
False CInt
0 Window
0 Window
0 CInt
0 CInt
0 Window
0 Window
0
        else do WMHints
x <- Ptr WMHints -> IO WMHints
forall a. Storable a => Ptr a -> IO a
peek Ptr WMHints
p; CInt
_ <- Ptr WMHints -> IO CInt
forall a. Ptr a -> IO CInt
xFree Ptr WMHints
p; WMHints -> IO WMHints
forall (m :: * -> *) a. Monad m => a -> m a
return WMHints
x

foreign import ccall unsafe "XlibExtras.h XAllocWMHints"
    xAllocWMHints :: IO (Ptr WMHints)

foreign import ccall unsafe "XlibExtras.h XSetWMHints"
    xSetWMHints :: Display -> Window -> Ptr WMHints -> IO Status

setWMHints :: Display -> Window -> WMHints -> IO Status
setWMHints :: Display -> Window -> WMHints -> IO CInt
setWMHints Display
dpy Window
w WMHints
wmh = do
    Ptr WMHints
p_wmh <- IO (Ptr WMHints)
xAllocWMHints
    Ptr WMHints -> WMHints -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke Ptr WMHints
p_wmh WMHints
wmh
    CInt
res <- Display -> Window -> Ptr WMHints -> IO CInt
xSetWMHints Display
dpy Window
w Ptr WMHints
p_wmh
    CInt
_ <- Ptr WMHints -> IO CInt
forall a. Ptr a -> IO CInt
xFree Ptr WMHints
p_wmh
    CInt -> IO CInt
forall (m :: * -> *) a. Monad m => a -> m a
return CInt
res

------------------------------------------------------------------------
-- Keysym Macros
--
-- Which we have to wrap in functions, then bind here.

foreign import ccall unsafe "XlibExtras.h x11_extras_IsCursorKey"
    isCursorKey :: KeySym -> Bool
foreign import ccall unsafe "XlibExtras.h x11_extras_IsFunctionKey"
    isFunctionKey :: KeySym -> Bool
foreign import ccall unsafe "XlibExtras.h x11_extras_IsKeypadKey"
    isKeypadKey :: KeySym -> Bool
foreign import ccall unsafe "XlibExtras.h x11_extras_IsMiscFunctionKey"
    isMiscFunctionKey :: KeySym -> Bool
foreign import ccall unsafe "XlibExtras.h x11_extras_IsModifierKey"
    isModifierKey :: KeySym -> Bool
foreign import ccall unsafe "XlibExtras.h x11_extras_IsPFKey"
    isPFKey :: KeySym -> Bool
foreign import ccall unsafe "XlibExtras.h x11_extras_IsPrivateKeypadKey"
    isPrivateKeypadKey :: KeySym -> Bool

-------------------------------------------------------------------------------
-- Selections
--
foreign import ccall unsafe "HsXlib.h XSetSelectionOwner"
    xSetSelectionOwner :: Display -> Atom -> Window -> Time -> IO ()

foreign import ccall unsafe "HsXlib.h XGetSelectionOwner"
    xGetSelectionOwner :: Display -> Atom -> IO Window

foreign import ccall unsafe "HsXlib.h XConvertSelection"
    xConvertSelection :: Display -> Atom -> Atom -> Atom -> Window -> Time -> IO ()

-------------------------------------------------------------------------------
-- Error handling
--
type XErrorEventPtr = Ptr ()
type CXErrorHandler = Display -> XErrorEventPtr -> IO CInt
type XErrorHandler = Display -> XErrorEventPtr -> IO ()

data ErrorEvent = ErrorEvent {
    ErrorEvent -> CInt
ev_type :: !CInt,
    ErrorEvent -> Display
ev_display :: Display,
    ErrorEvent -> CULong
ev_serialnum :: !CULong,
    ErrorEvent -> CUChar
ev_error_code :: !CUChar,
    ErrorEvent -> CUChar
ev_request_code :: !CUChar,
    ErrorEvent -> CUChar
ev_minor_code :: !CUChar,
    ErrorEvent -> Window
ev_resourceid :: !XID
}

foreign import ccall safe "wrapper"
    mkXErrorHandler :: CXErrorHandler -> IO (FunPtr CXErrorHandler)
foreign import ccall safe "dynamic"
    getXErrorHandler :: FunPtr CXErrorHandler -> CXErrorHandler
foreign import ccall safe "HsXlib.h XSetErrorHandler"
    _xSetErrorHandler :: FunPtr CXErrorHandler -> IO (FunPtr CXErrorHandler)

-- |A binding to XSetErrorHandler.
--  NOTE:  This is pretty experimental because of safe vs. unsafe calls.  I
--  changed sync to a safe call, but there *might* be other calls that cause a
--  problem
setErrorHandler :: XErrorHandler -> IO ()
setErrorHandler :: XErrorHandler -> IO ()
setErrorHandler XErrorHandler
new_handler = do
    FunPtr CXErrorHandler
_handler <- CXErrorHandler -> IO (FunPtr CXErrorHandler)
mkXErrorHandler (\Display
d -> \Ptr ()
e -> XErrorHandler
new_handler Display
d Ptr ()
e IO () -> IO CInt -> IO CInt
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> CInt -> IO CInt
forall (m :: * -> *) a. Monad m => a -> m a
return CInt
0)
    FunPtr CXErrorHandler
_ <- FunPtr CXErrorHandler -> IO (FunPtr CXErrorHandler)
_xSetErrorHandler FunPtr CXErrorHandler
_handler
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

-- |Retrieves error event data from a pointer to an XErrorEvent and
--  puts it into an ErrorEvent.
getErrorEvent :: XErrorEventPtr -> IO ErrorEvent
getErrorEvent :: Ptr () -> IO ErrorEvent
getErrorEvent Ptr ()
ev_ptr = do
    CInt
_type <- (\Ptr ()
hsc_ptr -> Ptr () -> Int -> IO CInt
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr ()
hsc_ptr Int
0) Ptr ()
ev_ptr
{-# LINE 1701 "Graphics/X11/Xlib/Extras.hsc" #-}
    serial <- (\hsc_ptr -> peekByteOff hsc_ptr 24) ev_ptr
{-# LINE 1702 "Graphics/X11/Xlib/Extras.hsc" #-}
    dsp <- fmap Display ((\hsc_ptr -> peekByteOff hsc_ptr 8) ev_ptr)
{-# LINE 1703 "Graphics/X11/Xlib/Extras.hsc" #-}
    error_code <- (\hsc_ptr -> peekByteOff hsc_ptr 32) ev_ptr
{-# LINE 1704 "Graphics/X11/Xlib/Extras.hsc" #-}
    request_code <- (\hsc_ptr -> peekByteOff hsc_ptr 33) ev_ptr
{-# LINE 1705 "Graphics/X11/Xlib/Extras.hsc" #-}
    minor_code <- (\hsc_ptr -> peekByteOff hsc_ptr 34) ev_ptr
{-# LINE 1706 "Graphics/X11/Xlib/Extras.hsc" #-}
    resourceid <- (\hsc_ptr -> peekByteOff hsc_ptr 16) ev_ptr
{-# LINE 1707 "Graphics/X11/Xlib/Extras.hsc" #-}
    return $ ErrorEvent {
        ev_type = _type,
        ev_display = dsp,
        ev_serialnum = serial,
        ev_error_code = error_code,
        ev_request_code = request_code,
        ev_minor_code = minor_code,
        ev_resourceid = resourceid
    }

-- |A binding to XMapRaised.
foreign import ccall unsafe "HsXlib.h XMapRaised"
    mapRaised :: Display -> Window -> IO CInt

foreign import ccall unsafe "HsXlib.h XGetCommand"
    xGetCommand :: Display -> Window -> Ptr (Ptr CWString) -> Ptr CInt -> IO Status

getCommand :: Display -> Window -> IO [String]
getCommand :: Display -> Window -> IO [String]
getCommand Display
d Window
w =
  (Ptr (Ptr CWString) -> IO [String]) -> IO [String]
forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca ((Ptr (Ptr CWString) -> IO [String]) -> IO [String])
-> (Ptr (Ptr CWString) -> IO [String]) -> IO [String]
forall a b. (a -> b) -> a -> b
$
  \Ptr (Ptr CWString)
argvp ->
  (Ptr CInt -> IO [String]) -> IO [String]
forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca ((Ptr CInt -> IO [String]) -> IO [String])
-> (Ptr CInt -> IO [String]) -> IO [String]
forall a b. (a -> b) -> a -> b
$
  \Ptr CInt
argcp ->
  do
    CInt
_ <- (CInt -> Bool) -> (CInt -> String) -> IO CInt -> IO CInt
forall a. (a -> Bool) -> (a -> String) -> IO a -> IO a
throwIf (CInt
success CInt -> CInt -> Bool
forall a. Ord a => a -> a -> Bool
>) (\CInt
status -> String
"xGetCommand returned status: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ CInt -> String
forall a. Show a => a -> String
show CInt
status) (IO CInt -> IO CInt) -> IO CInt -> IO CInt
forall a b. (a -> b) -> a -> b
$ Display -> Window -> Ptr (Ptr CWString) -> Ptr CInt -> IO CInt
xGetCommand Display
d Window
w Ptr (Ptr CWString)
argvp Ptr CInt
argcp
    CInt
argc <- Ptr CInt -> IO CInt
forall a. Storable a => Ptr a -> IO a
peek Ptr CInt
argcp
    Ptr CWString
argv <- Ptr (Ptr CWString) -> IO (Ptr CWString)
forall a. Storable a => Ptr a -> IO a
peek Ptr (Ptr CWString)
argvp
    [String]
texts <- ((Int -> IO String) -> [Int] -> IO [String])
-> [Int] -> (Int -> IO String) -> IO [String]
forall a b c. (a -> b -> c) -> b -> a -> c
flip (Int -> IO String) -> [Int] -> IO [String]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM [Int
0 .. CInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (CInt -> Int) -> CInt -> Int
forall a b. (a -> b) -> a -> b
$ CInt -> CInt
forall a. Enum a => a -> a
pred CInt
argc] ((Int -> IO String) -> IO [String])
-> (Int -> IO String) -> IO [String]
forall a b. (a -> b) -> a -> b
$ \Int
i -> Ptr CWString -> Int -> IO CWString
forall a. Storable a => Ptr a -> Int -> IO a
peekElemOff Ptr CWString
argv Int
i IO CWString -> (CWString -> IO String) -> IO String
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= CWString -> IO String
peekCWString
    Ptr CWString -> IO ()
wcFreeStringList Ptr CWString
argv
    [String] -> IO [String]
forall (m :: * -> *) a. Monad m => a -> m a
return [String]
texts

foreign import ccall unsafe "HsXlib.h XGetModifierMapping"
    xGetModifierMapping :: Display -> IO (Ptr ())

foreign import ccall unsafe "HsXlib.h XFreeModifiermap"
    xFreeModifiermap :: Ptr () -> IO (Ptr CInt)

getModifierMapping :: Display -> IO [(Modifier, [KeyCode])]
getModifierMapping :: Display -> IO [(KeyMask, [KeyCode])]
getModifierMapping Display
d = do
    Ptr ()
p <- Display -> IO (Ptr ())
xGetModifierMapping Display
d
    CInt
m' <- (\Ptr ()
hsc_ptr -> Ptr () -> Int -> IO CInt
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr ()
hsc_ptr Int
0) Ptr ()
p :: IO CInt
{-# LINE 1748 "Graphics/X11/Xlib/Extras.hsc" #-}
    let m = fromIntegral m'
    Ptr KeyCode
pks <- (\Ptr ()
hsc_ptr -> Ptr () -> Int -> IO (Ptr KeyCode)
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr ()
hsc_ptr Int
8) Ptr ()
p :: IO (Ptr KeyCode)
{-# LINE 1750 "Graphics/X11/Xlib/Extras.hsc" #-}
    ks <- peekArray (m * 8) pks
    Ptr CInt
_ <- Ptr () -> IO (Ptr CInt)
xFreeModifiermap Ptr ()
p
    [(KeyMask, [KeyCode])] -> IO [(KeyMask, [KeyCode])]
forall (m :: * -> *) a. Monad m => a -> m a
return ([(KeyMask, [KeyCode])] -> IO [(KeyMask, [KeyCode])])
-> (([KeyCode], [KeyCode]) -> [(KeyMask, [KeyCode])])
-> ([KeyCode], [KeyCode])
-> IO [(KeyMask, [KeyCode])]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [KeyMask] -> [[KeyCode]] -> [(KeyMask, [KeyCode])]
forall a b. [a] -> [b] -> [(a, b)]
zip [KeyMask]
masks ([[KeyCode]] -> [(KeyMask, [KeyCode])])
-> (([KeyCode], [KeyCode]) -> [[KeyCode]])
-> ([KeyCode], [KeyCode])
-> [(KeyMask, [KeyCode])]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (([KeyCode], [KeyCode]) -> [KeyCode])
-> [([KeyCode], [KeyCode])] -> [[KeyCode]]
forall a b. (a -> b) -> [a] -> [b]
map ([KeyCode], [KeyCode]) -> [KeyCode]
forall a b. (a, b) -> a
fst ([([KeyCode], [KeyCode])] -> [[KeyCode]])
-> (([KeyCode], [KeyCode]) -> [([KeyCode], [KeyCode])])
-> ([KeyCode], [KeyCode])
-> [[KeyCode]]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [([KeyCode], [KeyCode])] -> [([KeyCode], [KeyCode])]
forall a. [a] -> [a]
tail ([([KeyCode], [KeyCode])] -> [([KeyCode], [KeyCode])])
-> (([KeyCode], [KeyCode]) -> [([KeyCode], [KeyCode])])
-> ([KeyCode], [KeyCode])
-> [([KeyCode], [KeyCode])]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (([KeyCode], [KeyCode]) -> ([KeyCode], [KeyCode]))
-> ([KeyCode], [KeyCode]) -> [([KeyCode], [KeyCode])]
forall a. (a -> a) -> a -> [a]
iterate (Int -> [KeyCode] -> ([KeyCode], [KeyCode])
forall a. Int -> [a] -> ([a], [a])
splitAt Int
m ([KeyCode] -> ([KeyCode], [KeyCode]))
-> (([KeyCode], [KeyCode]) -> [KeyCode])
-> ([KeyCode], [KeyCode])
-> ([KeyCode], [KeyCode])
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ([KeyCode], [KeyCode]) -> [KeyCode]
forall a b. (a, b) -> b
snd) (([KeyCode], [KeyCode]) -> IO [(KeyMask, [KeyCode])])
-> ([KeyCode], [KeyCode]) -> IO [(KeyMask, [KeyCode])]
forall a b. (a -> b) -> a -> b
$ ([], [KeyCode]
ks)
 where
    masks :: [KeyMask]
masks = [KeyMask
shiftMapIndex .. KeyMask
mod5MapIndex]