1{-# LANGUAGE ScopedTypeVariables #-}
2-- -*-haskell-*-
3
4#include <gtk/gtk.h>
5#include "template-hsc-gtk2hs.h"
6
7--  GIMP Toolkit (GTK) GDK Events
8--
9--  Author : Axel Simon
10--
11--  Created: 27 April 2001
12--
13--  Copyright (C) 2001-2005 Axel Simon
14--
15--  This library is free software; you can redistribute it and/or
16--  modify it under the terms of the GNU Lesser General Public
17--  License as published by the Free Software Foundation; either
18--  version 2.1 of the License, or (at your option) any later version.
19--
20--  This library is distributed in the hope that it will be useful,
21--  but WITHOUT ANY WARRANTY; without even the implied warranty of
22--  MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
23--  Lesser General Public License for more details.
24--
25-- |
26-- Maintainer  : gtk2hs-users\@lists.sourceforge.net
27-- Stability   : deprecated
28-- Portability : portable (depends on GHC)
29--
30-- Definiton of a record that contains event information. Deprecated in
31-- favor of 'Graphics.UI.Gtk.Gdk.EventM' and not exported by Gtk.hs.
32--
33module Graphics.UI.Gtk.Gdk.Events (
34  Modifier(..),         -- a mask of control keys
35  TimeStamp,
36  currentTime,
37
38  -- | Deprecated way of conveying event information.
39  Event(..),            -- information in event callbacks from Gdk
40  EventButton,
41  EventScroll,
42  EventMotion,
43  EventExpose,
44  EventKey,
45  EventConfigure,
46  EventCrossing,
47  EventFocus,
48  EventProperty,
49  EventProximity,
50  EventVisibility,
51  EventWindowState,
52  EventGrabBroken,
53
54  marshExposeRect,
55
56  -- selector functions
57  marshalEvent,         -- convert a pointer to an event data structure
58  -- used data structures
59  VisibilityState(..),
60  CrossingMode(..),
61  NotifyType(..),
62  WindowState(..),
63  ScrollDirection(..),
64  MouseButton(..),
65  Click(..),
66  Rectangle(..)
67  ) where
68
69import System.IO.Unsafe (unsafeInterleaveIO)
70import System.Glib.FFI
71import System.Glib.UTFString
72import System.Glib.Flags
73import Graphics.UI.Gtk.Gdk.Keys         (KeyVal, keyvalToChar, keyvalName)
74#if GTK_MAJOR_VERSION < 3
75import Graphics.UI.Gtk.Gdk.Region       (Region, makeNewRegion)
76#endif
77import Graphics.UI.Gtk.Gdk.Enums        (Modifier(..),
78                                         VisibilityState(..),
79                                         CrossingMode(..),
80                                         NotifyType(..),
81                                         WindowState(..),
82                                         ScrollDirection(..))
83import Graphics.UI.Gtk.General.Enums    (MouseButton(..), Click(..))
84import Graphics.UI.Gtk.General.Structs  (Rectangle(..))
85
86-- | The time (in milliseconds) when an event happened. This is used mostly
87-- for ordering events and responses to events.
88--
89type TimeStamp = Word32
90-- TODO: make this a newtype
91
92-- | Represents the current time, and can be used anywhere a time is expected.
93currentTime :: TimeStamp
94currentTime = #{const GDK_CURRENT_TIME}
95
96-- Note on Event:
97-- * 'Event' can communicate a small array of data to another widget. This
98--   functionality is not bound as it can be done easier in Haskell.
99--
100-- * EventDND is not implemented as registering a DND source or sink
101--   should be easier and sufficient for everything.
102--
103-- * EventProperty is not bound since it involves Atoms and its hard to see
104--   how a Haskell application should extract the data. It should be possible
105--   to connect directly to 'propertyChanged' signals. If there is a need
106--   to monitor a property for which there is no signal we could add
107--   a trigger for just that property.
108--
109-- * EventSelection - I don\'t quite see how this works, so not bound.
110--
111-- * NoExpose - seems pointless: you copy from a drawable and this signal
112--   tells you that it was up-to-date without redrawing. Maybe I'm missing
113--   something.
114--
115-- * EventSetting informs about a change in setting that are shared among
116--   several applications. They are probably not relevant to user defined
117--   widgets. Anyway they don\'t make sense before GtkSettings isn\'t bound.
118--
119-- * Property is a TODO. These come from RC files which are useful for
120--   custom widgets.
121
122-- | An event that contains information on a button press.
123type EventButton = Event
124
125-- | An event that contains information on scrolling.
126type EventScroll = Event
127
128-- | An event that contains information on the movement of the mouse pointer.
129type EventMotion = Event
130
131-- | An area of the 'DrawWindow' needs redrawing.
132type EventExpose = Event
133
134-- | An event that contains information about a key press.
135type EventKey = Event
136
137-- | An event that contains the new size of a window.
138type EventConfigure = Event
139
140-- | Generated when the pointer enters or leaves a window.
141type EventCrossing = Event
142
143-- | An event that informs about a change of the input focus.
144type EventFocus = Event
145
146-- | An event that indicates a property of the window changed.
147type EventProperty = Event
148
149-- | An event that indicates that the pen of a graphics table is touching or
150--   not touching the tablet.
151type EventProximity = Event
152
153-- | Parts of the window have been exposed or obscured.
154type EventVisibility = Event
155
156-- | The window state has changed.
157type EventWindowState = Event
158
159-- | A grab has been broken by unusual means.
160type EventGrabBroken = Event
161
162-- | Events that are delivered to a widget.
163--
164-- * Any given signal only emits one of these variants as described
165--   in 'Graphics.UI.Gtk.Abstract.Widget.Widget'.
166--   Many events share common attributes:
167--
168--   * The 'eventSent' attribute is @True@ if the event was not created by the
169--      user but by another application.
170--
171--   * The 'eventTime' attribute contains a time in milliseconds when the event
172--      happened.
173--
174--   * The 'eventX' and 'eventY' attributes contain the coordinates relative
175--      to the 'Graphics.UI.Gtk.Abstract.Gdk.DrawWindow' associated with this
176--      widget. The values can contain sub-pixel information if the input
177--      device is a graphics tablet or the like.
178--
179--   * The 'eventModifier' attribute denotes what modifier key was pressed
180--      during the event.
181--
182data Event =
183  -- | An event that is not in one of the more specific categories below. This
184  -- includes delete, destroy, map and unmap events. These events
185  -- have no extra information associated with them.
186  Event { eventSent :: Bool }
187  -- | The expose event.
188  --
189  -- * A region of widget that receives this event needs to be redrawn.
190  --   This event is the result of revealing part or all of a window
191  --   or by the application calling functions like
192  --   'Graphics.UI.Gtk.Abstract.Widget.widgetQueueDrawArea'.
193  --
194  | Expose {
195    eventSent   :: Bool,
196    -- | A bounding box denoting what needs to be updated. For a more
197    -- detailed information on the area that needs redrawing, use the
198    -- next field.
199    eventArea   :: Rectangle,
200#if GTK_MAJOR_VERSION < 3
201    -- | A set of horizontal stripes that denote the invalid area.
202    eventRegion      :: Region,
203#endif
204
205    -- | The number of contiguous 'Expose' events following this
206    --   one. The only use for this is \"exposure compression\", i.e.
207    --   handling all contiguous 'Expose' events in one go, though Gdk
208    --   performs some exposure compression so this is not normally needed.
209    eventCount  :: Int }
210  -- | Mouse motion.
211  --
212  -- * Captures the movement of the mouse cursor while it is within the area
213  --   of the widget.
214  --
215  | Motion {
216    eventSent   :: Bool,
217    eventTime   :: TimeStamp,
218    eventX,eventY       :: Double,
219    eventModifier       :: [Modifier],
220    -- | Indicate if this event is only a hint of the motion.
221    --
222    -- * If the 'Graphics.UI.Gtk.Abstract.Widget.PointerMotionHintMask'
223    --  is set with 'Data.Array.MArray.widgetAddEvents' then
224    --   mouse positions are only generated each time
225    --  'Graphics.UI.Gtk.Gdk.DrawWindow.drawWindowGetPointer'
226    --   is called. In this case 'eventIsHint' is set to @True@.
227    --
228    eventIsHint :: Bool,
229    eventXRoot,
230    eventYRoot  :: Double }
231  -- | A mouse button was pressed or released.
232  --
233  -- * This event is triggered if the mouse button was pressed or released
234  --   while the mouse cursor was within the region of the widget.
235  --
236  | Button {
237    eventSent   :: Bool,
238    -- | The kind of button press, see 'Click'. Note that double clicks will
239    --   trigger this event with 'eventClick' set to 'SingleClick',
240    --   'ReleaseClick',
241    --   'SingleClick', 'DoubleClick', 'ReleaseClick'. Triple clicks will
242    --   produce this sequence followed by 'SingleClick', 'DoubleClick',
243    --   'TripleClick', 'ReleaseClick'.
244    eventClick  :: Click,
245    -- | The time of the event in milliseconds.
246    eventTime   :: TimeStamp,
247    eventX,eventY       :: Double,
248    eventModifier       :: [Modifier],
249    -- | The button that was pressed.
250    eventButton :: MouseButton,
251    -- | The coordinates of the click relative to the screen origin.
252    eventXRoot,
253    eventYRoot  :: Double }
254  -- | A key was pressed while the widget had the input focus.
255  --
256  -- * If the widget has the current input focus (see
257  --   'Graphics.UI.Gtk.Abstract.Widget.widgetSetCanFocus')
258  --   it will receive key pressed events. Certain key combinations are of
259  --   no interest to a normal widget like Alt-F to access the file menu.
260  --   For all these keys, the handler must return @False@ to indicate that
261  --   the key stroke should be propagated to the parent widget. At the
262  --   top-level widget, keyboard shortcuts like Alt-F are turned into the
263  --   corresponding signals.
264  --
265  | Key {
266    -- | This flag is set if the key was released. This flag makes it possible
267    --   to connect the same handler to
268    --  'Graphics.UI.Gtk.Abstract.Widget.onKeyPress' and
269    --  'Graphics.UI.Gtk.Abstract.Widget.onKeyRelease'.
270    eventRelease        :: Bool,
271    eventSent   :: Bool,
272    eventTime   :: TimeStamp,
273    eventModifier       :: [Modifier],
274    -- | This flag is @True@ if Caps Lock is on while this key was pressed.
275    eventWithCapsLock   :: Bool,
276    -- | This flag is @True@ if Number Lock is on while this key was pressed.
277    eventWithNumLock    :: Bool,
278    -- | This flag is @True@ if Scroll Lock is on while this key was pressed.
279    eventWithScrollLock :: Bool,
280    -- | A number representing the key that was pressed or released. A more convenient
281    --   interface is provided by the next two fields.
282    eventKeyVal :: KeyVal,
283    -- | A string representing the key that was pressed or released.
284    --
285    -- * This string contains a description of the key rather than what
286    --   should appear on screen. For example, pressing "1" on the keypad
287    --   results in "KP_1". Of particular interest are "F1" till "F12",
288    --   for a complete list refer to \"<gdk/gdkkeysyms.h>\" where all
289    --   possible values are defined. The corresponding strings are the
290    --   constants without the GDK_ prefix.
291    eventKeyName :: DefaultGlibString,
292    -- | A character matching the key that was pressed.
293    --
294    -- * This entry can be used to build up a whole input string.
295    --   The character is @Nothing@ if the key does not correspond to a simple
296    --   unicode character.
297    --
298    eventKeyChar     :: Maybe Char }
299  -- | Mouse cursor crossing event.
300  --
301  -- * This event indicates that the mouse cursor is hovering over this
302  --   widget. It is used to set a widget into the pre-focus state where
303  --   some GUI elements like buttons on a toolbar change their appearance.
304  --
305  | Crossing {
306    eventSent   :: Bool,
307    eventTime   :: TimeStamp,
308    eventX,eventY       :: Double,
309    eventXRoot,
310    eventYRoot  :: Double,
311    -- | This flag is false if the widget was entered, it is true when the
312    --   widget the mouse cursor left the widget.
313    eventLeaves :: Bool,
314    -- | Kind of enter\/leave event.
315    --
316    -- * The mouse cursor might enter this widget because it grabs the mouse
317    --   cursor for e.g. a modal dialog box.
318    --
319    eventCrossingMode   :: CrossingMode,
320    -- | Information on from what level of the widget hierarchy the mouse
321    --   cursor came.
322    --
323    -- * See 'NotifyType'.
324    --
325    eventNotifyType     :: NotifyType,
326    eventModifier       :: [Modifier]}
327  -- | Gaining or loosing input focus.
328  --
329  | Focus {
330    eventSent   :: Bool,
331    -- | This flag is @True@ if the widget receives the focus and @False@ if
332    -- it just lost the input focus.
333    eventInFocus        :: Bool}
334  -- | The widget\'s size has changed.
335  --
336  -- * In response to this event the application can allocate resources that
337  --   are specific to the size of the widget. It is emitted when the widget
338  --   is shown the first time and on every resize.
339  --
340  | Configure {
341    eventSent   :: Bool,
342    -- | Position within the parent window.
343    eventXParent        :: Int,
344    -- | Position within the parent window.
345    eventYParent        :: Int,
346    eventWidth  :: Int,
347    eventHeight :: Int}
348  -- | Change of visibility of a widget.
349  | Visibility {
350    eventSent   :: Bool,
351    -- | Denote what portions of the widget is visible.
352    eventVisible        :: VisibilityState }
353  -- | Wheel movement of the mouse.
354  --
355  -- * This action denotes that the content of the widget should be scrolled.
356  --   The event is triggered by the movement of the mouse wheel. Surrounding
357  --   scroll bars are independant of this signal. Most mice do not have
358  --   buttons for horizontal scrolling, hence 'eventDirection' will usually not
359  --   contain 'ScrollLeft' and 'ScrollRight'. Mice with additional
360  --   buttons may not work on X since only five buttons are supported
361  --   (the three main buttons and two for the wheel).
362  --
363  -- * The handler of this signal should update the scroll bars that
364  --   surround this widget which in turn tell this widget to update.
365  --
366  | Scroll {
367    eventSent   :: Bool,
368    eventTime   :: TimeStamp,
369    eventX,eventY       :: Double,
370    eventDirection      :: ScrollDirection,
371    eventXRoot,
372    eventYRoot  :: Double}
373  -- | Indicate how the appearance of this window has changed.
374  | WindowState {
375    eventSent   :: Bool,
376    -- | The mask indicates which flags have changed.
377    eventWindowMask     :: [WindowState],
378    -- | The state indicates the current state of the window.
379    eventWindowState    :: [WindowState]}
380  -- | The state of the pen of a graphics tablet pen or touchscreen device.
381  | Proximity {
382    eventSent   :: Bool,
383    eventTime   :: TimeStamp,
384    -- | Whether the stylus has moved in or out of contact with the tablet.
385    eventInContact     :: Bool
386  } deriving Show
387
388marshalEvent :: Ptr Event -> IO Event
389marshalEvent ptr = do
390  (eType::#gtk2hs_type GdkEventType) <- #{peek GdkEventAny,type} ptr
391  (case eType of
392    #{const GDK_DELETE}         -> marshAny
393    #{const GDK_DESTROY}        -> marshAny
394    #{const GDK_EXPOSE}         -> marshExpose
395    #{const GDK_MOTION_NOTIFY}  -> marshMotion
396    #{const GDK_BUTTON_PRESS}   -> marshButton SingleClick
397    #{const GDK_2BUTTON_PRESS}  -> marshButton DoubleClick
398    #{const GDK_3BUTTON_PRESS}  -> marshButton TripleClick
399    #{const GDK_BUTTON_RELEASE} -> marshButton ReleaseClick
400    #{const GDK_KEY_PRESS}      -> marshKey False
401    #{const GDK_KEY_RELEASE}    -> marshKey True
402    #{const GDK_ENTER_NOTIFY}   -> marshCrossing False
403    #{const GDK_LEAVE_NOTIFY}   -> marshCrossing True
404    #{const GDK_FOCUS_CHANGE}   -> marshFocus
405    #{const GDK_CONFIGURE}      -> marshConfigure
406    #{const GDK_MAP}            -> marshAny
407    #{const GDK_UNMAP}          -> marshAny
408--    #{const GDK_PROPERTY_NOTIFY}-> marshProperty
409    #{const GDK_PROXIMITY_IN}   -> marshProximity True
410    #{const GDK_PROXIMITY_OUT}  -> marshProximity False
411    #{const GDK_VISIBILITY_NOTIFY}-> marshVisibility
412    #{const GDK_SCROLL}         -> marshScroll
413    #{const GDK_WINDOW_STATE}   -> marshWindowState
414    code                        -> \_ -> fail $
415      "marshalEvent: unhandled event type " ++ show code ++
416      "\nplease report this as a bug to gtk2hs-devel@lists.sourceforge.net"
417    ) ptr
418
419marshAny ptr = do
420  (sent   ::#gtk2hs_type gint8) <- #{peek GdkEventAny, send_event} ptr
421  return Event {
422    eventSent = toBool sent
423  }
424
425marshExpose ptr = do
426  (#{const GDK_EXPOSE}::#gtk2hs_type GdkEventType) <- #{peek GdkEventAny,type} ptr
427  (sent_   ::#gtk2hs_type gint8)        <- #{peek GdkEventExpose, send_event} ptr
428  (area_   ::Rectangle)         <- #{peek GdkEventExpose, area} ptr
429#if GTK_MAJOR_VERSION < 3
430  (reg_   :: Ptr Region)        <- #{peek GdkEventExpose, region} ptr
431  reg_ <- gdk_region_copy reg_
432  region_ <- makeNewRegion reg_
433#endif
434  (count_  ::#gtk2hs_type gint) <- #{peek GdkEventExpose, count} ptr
435  return $ Expose {
436    eventSent   = toBool sent_,
437    eventArea   = area_,
438#if GTK_MAJOR_VERSION < 3
439    eventRegion = region_,
440#endif
441    eventCount  = fromIntegral count_}
442
443#if GTK_MAJOR_VERSION < 3
444foreign import ccall "gdk_region_copy"
445  gdk_region_copy :: Ptr Region -> IO (Ptr Region)
446#endif
447
448marshExposeRect :: Ptr Event -> IO Rectangle
449marshExposeRect ptr = do
450  (#{const GDK_EXPOSE}::#gtk2hs_type GdkEventType) <- #{peek GdkEventAny,type} ptr
451  (area_   ::Rectangle)         <- #{peek GdkEventExpose, area} ptr
452  return area_
453
454marshMotion ptr = do
455  (sent_   ::#gtk2hs_type gint8)        <- #{peek GdkEventMotion, send_event} ptr
456  (time_   ::#gtk2hs_type guint32)      <- #{peek GdkEventMotion, time} ptr
457  (x_      ::#gtk2hs_type gdouble)      <- #{peek GdkEventMotion, x} ptr
458  (y_      ::#gtk2hs_type gdouble)      <- #{peek GdkEventMotion, y} ptr
459  (modif_  ::#gtk2hs_type guint)        <- #{peek GdkEventMotion, state} ptr
460  (isHint_ ::#gtk2hs_type gint16)       <- #{peek GdkEventMotion, is_hint} ptr
461  (xRoot_  ::#gtk2hs_type gdouble)      <- #{peek GdkEventMotion, x_root} ptr
462  (yRoot_  ::#gtk2hs_type gdouble)      <- #{peek GdkEventMotion, y_root} ptr
463  return $ Motion {
464    eventSent   = toBool sent_,
465    eventTime   = fromIntegral time_,
466    eventX         = realToFrac x_,
467    eventY         = realToFrac y_,
468    eventModifier  = (toFlags . fromIntegral) modif_,
469    eventIsHint = toBool isHint_,
470    eventXRoot  = realToFrac xRoot_,
471    eventYRoot  = realToFrac yRoot_}
472
473marshButton but ptr = do
474  (sent_   ::#gtk2hs_type gint8)        <- #{peek GdkEventButton, send_event} ptr
475  (time_   ::#gtk2hs_type guint32)      <- #{peek GdkEventButton, time} ptr
476  (x_      ::#gtk2hs_type gdouble)      <- #{peek GdkEventButton, x} ptr
477  (y_      ::#gtk2hs_type gdouble)      <- #{peek GdkEventButton, y} ptr
478  (modif_  ::#gtk2hs_type guint)        <- #{peek GdkEventButton, state} ptr
479  (button_ ::#gtk2hs_type guint)        <- #{peek GdkEventButton, button} ptr
480  (xRoot_  ::#gtk2hs_type gdouble)      <- #{peek GdkEventButton, x_root} ptr
481  (yRoot_  ::#gtk2hs_type gdouble)      <- #{peek GdkEventButton, y_root} ptr
482  return $ Button {
483    eventClick  = but,
484    eventSent   = toBool sent_,
485    eventTime   = fromIntegral time_,
486    eventX         = realToFrac x_,
487    eventY         = realToFrac y_,
488    eventModifier  = (toFlags . fromIntegral) modif_,
489    eventButton = (toEnum.fromIntegral) button_,
490    eventXRoot  = realToFrac xRoot_,
491    eventYRoot  = realToFrac yRoot_}
492
493
494marshKey up ptr = do
495  (sent_   ::#gtk2hs_type gint8)        <- #{peek GdkEventKey, send_event} ptr
496  (time_   ::#gtk2hs_type guint32)      <- #{peek GdkEventKey, time} ptr
497  (modif_  ::#gtk2hs_type guint)        <- #{peek GdkEventKey, state} ptr
498  (keyval_ ::#gtk2hs_type guint)        <- #{peek GdkEventKey, keyval} ptr
499
500  (length_ ::#gtk2hs_type gint) <- #{peek GdkEventKey, length} ptr
501  keyChar <- keyvalToChar keyval_
502  keyName <- unsafeInterleaveIO $ keyvalName keyval_
503  return $ Key {
504    eventRelease = up,
505    eventSent = toBool sent_,
506    eventTime   = fromIntegral time_,
507    eventModifier  = (toFlags . fromIntegral) modif_,
508    eventWithCapsLock = (modif_ .&. #{const GDK_LOCK_MASK})/=0,
509    eventWithNumLock = (modif_ .&. #{const GDK_MOD2_MASK})/=0,
510    eventWithScrollLock = (modif_ .&. #{const GDK_MOD3_MASK})/=0,
511    eventKeyVal = keyval_,
512    eventKeyName = keyName,
513    eventKeyChar = keyChar }
514
515marshCrossing leave ptr = do
516  (sent_   ::#gtk2hs_type gint8)        <- #{peek GdkEventCrossing, send_event} ptr
517  (time_   ::#gtk2hs_type guint32)      <- #{peek GdkEventCrossing, time} ptr
518  (x_      ::#gtk2hs_type gdouble)      <- #{peek GdkEventCrossing, x} ptr
519  (y_      ::#gtk2hs_type gdouble)      <- #{peek GdkEventCrossing, y} ptr
520  (modif_  ::#gtk2hs_type guint)        <- #{peek GdkEventCrossing, state} ptr
521  (xRoot_  ::#gtk2hs_type gdouble)      <- #{peek GdkEventCrossing, x_root} ptr
522  (yRoot_  ::#gtk2hs_type gdouble)      <- #{peek GdkEventCrossing, y_root} ptr
523  (cMode_  ::#gtk2hs_type GdkCrossingMode)
524                                <- #{peek GdkEventCrossing, mode} ptr
525  (nType_  ::#gtk2hs_type GdkNotifyType)
526                                <- #{peek GdkEventCrossing, detail} ptr
527  (modif_  ::#gtk2hs_type guint)        <- #{peek GdkEventCrossing, state} ptr
528  return $ Crossing {
529    eventSent   = toBool sent_,
530    eventTime   = fromIntegral time_,
531    eventX         = realToFrac x_,
532    eventY         = realToFrac y_,
533    eventXRoot  = realToFrac xRoot_,
534    eventYRoot  = realToFrac yRoot_,
535    eventLeaves = leave,
536    eventCrossingMode  = (toEnum.fromIntegral) cMode_,
537    eventNotifyType    = (toEnum.fromIntegral) nType_,
538    eventModifier      = (toFlags . fromIntegral) modif_}
539
540
541marshFocus ptr = do
542  (sent_   ::#gtk2hs_type gint8)        <- #{peek GdkEventFocus, send_event} ptr
543  (inFocus_::#gtk2hs_type gint16)       <- #{peek GdkEventFocus, in} ptr
544  return $ Focus {
545    eventSent   = toBool sent_,
546    eventInFocus= toBool inFocus_}
547
548marshConfigure ptr = do
549  (sent_   ::#gtk2hs_type gint8)        <- #{peek GdkEventConfigure, send_event} ptr
550  (xPar_   ::#gtk2hs_type gint) <- #{peek GdkEventConfigure, x} ptr
551  (yPar_   ::#gtk2hs_type gint) <- #{peek GdkEventConfigure, y} ptr
552  (width_  ::#gtk2hs_type gint) <- #{peek GdkEventConfigure, width} ptr
553  (height_ ::#gtk2hs_type gint) <- #{peek GdkEventConfigure, height} ptr
554  return $ Configure {
555    eventSent   = toBool sent_,
556    eventXParent   = fromIntegral xPar_,
557    eventYParent   = fromIntegral yPar_,
558    eventWidth  = fromIntegral width_,
559    eventHeight = fromIntegral height_}
560
561{-
562marshProperty ptr = do
563  (sent_   ::#gtk2hs_type gint8)        <- #{peek GdkEventProperty, send_event} ptr
564  (time_   ::#gtk2hs_type guint32)      <- #{peek GdkEventProperty, time} ptr
565  return $ Property {
566    eventSent   = toBool sent_,
567    eventTime   = fromIntegral time_}
568-}
569
570marshProximity contact ptr = do
571  (sent_   ::#gtk2hs_type gint8)        <- #{peek GdkEventProximity, send_event} ptr
572  (time_   ::#gtk2hs_type guint32)      <- #{peek GdkEventProximity, time} ptr
573  return $ Proximity {
574    eventSent   = toBool sent_,
575    eventTime   = fromIntegral time_,
576    eventInContact = contact}
577
578marshVisibility ptr = do
579  (sent_   ::#gtk2hs_type gint8)        <- #{peek GdkEventVisibility, send_event} ptr
580  (state_  ::#gtk2hs_type GdkVisibilityState)
581                                <- #{peek GdkEventVisibility, state} ptr
582  return $ Visibility {
583    eventSent   = toBool sent_,
584    eventVisible= (toEnum.fromIntegral) state_}
585
586marshScroll ptr = do
587  (sent_   ::#gtk2hs_type gint8)        <- #{peek GdkEventScroll, send_event} ptr
588  (time_   ::#gtk2hs_type guint32)      <- #{peek GdkEventScroll, time} ptr
589  (x_     ::#gtk2hs_type gdouble)       <- #{peek GdkEventScroll, x} ptr
590  (y_     ::#gtk2hs_type gdouble)       <- #{peek GdkEventScroll, y} ptr
591  (direc_  ::#gtk2hs_type GdkScrollDirection)
592                                <- #{peek GdkEventScroll, direction} ptr
593  (xRoot_  ::#gtk2hs_type gdouble)      <- #{peek GdkEventScroll, x_root} ptr
594  (yRoot_  ::#gtk2hs_type gdouble)      <- #{peek GdkEventScroll, y_root} ptr
595  return $ Scroll {
596    eventSent   = toBool sent_,
597    eventTime   = fromIntegral time_,
598    eventX         = realToFrac x_,
599    eventY         = realToFrac y_,
600    eventDirection  = (toEnum.fromIntegral) direc_,
601    eventXRoot  = realToFrac xRoot_,
602    eventYRoot  = realToFrac yRoot_}
603
604
605marshWindowState ptr = do
606  (sent_   ::#gtk2hs_type gint8)        <- #{peek GdkEventWindowState, send_event} ptr
607  (wMask_  ::#gtk2hs_type GdkWindowState)
608                        <- #{peek GdkEventWindowState, changed_mask} ptr
609  (wState_ ::#gtk2hs_type GdkWindowState)
610                        <- #{peek GdkEventWindowState, new_window_state} ptr
611  return $ WindowState {
612    eventSent   = toBool sent_,
613    eventWindowMask  = (toFlags.fromIntegral) wMask_,
614    eventWindowState = (toFlags.fromIntegral) wState_}
615
616