{-# LINE 2 "./Graphics/UI/Gtk/Gdk/DrawWindow.chs" #-}
-- -*-haskell-*-
-- GIMP Toolkit (GTK) DrawWindow
--
-- Author : Axel Simon
--
-- Created: 5 November 2002
--
-- Copyright (C) 2002-2005 Axel Simon
--
-- This library is free software; you can redistribute it and/or
-- modify it under the terms of the GNU Lesser General Public
-- License as published by the Free Software Foundation; either
-- version 2.1 of the License, or (at your option) any later version.
--
-- This library is distributed in the hope that it will be useful,
-- but WITHOUT ANY WARRANTY; without even the implied warranty of
-- MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU
-- Lesser General Public License for more details.
--
-- |
-- Maintainer : gtk2hs-users@lists.sourceforge.net
-- Stability : provisional
-- Portability : portable (depends on GHC)
--
-- A 'DrawWindow' is a rectangular region on the screen.
--
module Graphics.UI.Gtk.Gdk.DrawWindow (
-- A 'DrawWindow' is used to implement high-level objects such as 'Widget' and
-- 'Window' on the Gtk+ level.
--
-- Most widgets draws its content into a 'DrawWindow', in particular
-- 'DrawingArea' is nothing but a widget that contains a 'DrawWindow'.
-- This object derives from 'Drawable' which defines the basic drawing
-- primitives.

-- * Class Hierarchy
-- |
-- @
-- | 'GObject'
-- | +----'Drawable'
-- | +----DrawWindow
-- @
--

-- * Types
  DrawWindow,
  DrawWindowClass,
  castToDrawWindow, gTypeDrawWindow,
  WindowState(..),
  NativeWindowId,
  toNativeWindowId,
  fromNativeWindowId,
-- * Methods
  drawWindowGetState,
  drawWindowScroll,
  drawWindowClear,
  drawWindowClearArea,
  drawWindowClearAreaExpose,
  drawWindowRaise,
  drawWindowLower,
  drawWindowBeginPaintRect,
  drawWindowBeginPaintRegion,
  drawWindowEndPaint,
  drawWindowInvalidateRect,
  drawWindowInvalidateRegion,
  drawWindowGetUpdateArea,
  drawWindowFreezeUpdates,
  drawWindowThawUpdates,
  drawWindowProcessUpdates,

  drawWindowSetAcceptFocus,

  drawWindowShapeCombineMask,
  drawWindowShapeCombineRegion,
  drawWindowSetChildShapes,
  drawWindowMergeChildShapes,
  drawWindowGetPointer,
  drawWindowGetPointerPos,
  drawWindowGetOrigin,
  drawWindowForeignNew,
  drawWindowGetDefaultRootWindow,
  ) where

import Control.Monad (liftM)

import System.Glib.FFI
import System.Glib.Flags (toFlags)
import System.Glib.GObject (wrapNewGObject,makeNewGObject)
import Graphics.UI.Gtk.Types
{-# LINE 91 "./Graphics/UI/Gtk/Gdk/DrawWindow.chs" #-}
import Graphics.UI.Gtk.Gdk.Enums
{-# LINE 92 "./Graphics/UI/Gtk/Gdk/DrawWindow.chs" #-}
import Graphics.UI.Gtk.Gdk.Region
{-# LINE 93 "./Graphics/UI/Gtk/Gdk/DrawWindow.chs" #-}
import Graphics.UI.Gtk.Gdk.EventM (Modifier, eventRegion)
import Graphics.UI.Gtk.General.Structs
import Graphics.UI.Gtk.Abstract.Widget (widgetSetDoubleBuffered)


{-# LINE 98 "./Graphics/UI/Gtk/Gdk/DrawWindow.chs" #-}

-- | Gets the bitwise OR of the currently active drawWindow state flags, from
-- the 'WindowState' enumeration.
--
drawWindowGetState :: DrawWindowClass self => self
 -> IO [WindowState] -- ^ returns @DrawWindow@ flags
drawWindowGetState self =
  liftM (toFlags . fromIntegral) $
  (\(DrawWindow arg1) -> withForeignPtr arg1 $ \argPtr1 ->gdk_window_get_state argPtr1)
{-# LINE 107 "./Graphics/UI/Gtk/Gdk/DrawWindow.chs" #-}
     (toDrawWindow self)

-- | Scroll the contents of @DrawWindow@.
--
-- * Scroll both, pixels and children, by the given amount.
-- @DrawWindow@ itself does not move. Portions of the window that the
-- scroll operation brings inm from offscreen areas are invalidated. The
-- invalidated region may be bigger than what would strictly be necessary. (For
-- X11, a minimum area will be invalidated if the window has no subwindows, or
-- if the edges of the window's parent do not extend beyond the edges of the
-- drawWindow. In other cases, a multi-step process is used to scroll the window
-- which may produce temporary visual artifacts and unnecessary invalidations.)
--
drawWindowScroll :: DrawWindowClass self => self
 -> Int -- ^ @dx@ - Amount to scroll in the X direction
 -> Int -- ^ @dy@ - Amount to scroll in the Y direction
 -> IO ()
drawWindowScroll self dx dy =
  (\(DrawWindow arg1) arg2 arg3 -> withForeignPtr arg1 $ \argPtr1 ->gdk_window_scroll argPtr1 arg2 arg3)
{-# LINE 126 "./Graphics/UI/Gtk/Gdk/DrawWindow.chs" #-}
     (toDrawWindow self)
     (fromIntegral dx)
     (fromIntegral dy)


-- | Clears an entire @DrawWindow@ to the background color or background pixmap.
--
drawWindowClear :: DrawWindowClass self => self -> IO ()
drawWindowClear self =
  (\(DrawWindow arg1) -> withForeignPtr arg1 $ \argPtr1 ->gdk_window_clear argPtr1)
{-# LINE 136 "./Graphics/UI/Gtk/Gdk/DrawWindow.chs" #-}
     (toDrawWindow self)

-- | Clears an area of @DrawWindow@ to the background color or background pixmap.
--
drawWindowClearArea :: DrawWindowClass self => self
 -> Int -- ^ @x@ - x coordinate of rectangle to clear
 -> Int -- ^ @y@ - y coordinate of rectangle to clear
 -> Int -- ^ @width@ - width of rectangle to clear
 -> Int -- ^ @height@ - height of rectangle to clear
 -> IO ()
drawWindowClearArea self x y width height =
  (\(DrawWindow arg1) arg2 arg3 arg4 arg5 -> withForeignPtr arg1 $ \argPtr1 ->gdk_window_clear_area argPtr1 arg2 arg3 arg4 arg5)
{-# LINE 148 "./Graphics/UI/Gtk/Gdk/DrawWindow.chs" #-}
     (toDrawWindow self)
     (fromIntegral x)
     (fromIntegral y)
     (fromIntegral width)
     (fromIntegral height)

-- | Like 'drawWindowClearArea', but also generates an expose event for the
-- cleared area.
--
drawWindowClearAreaExpose :: DrawWindowClass self => self
 -> Int -- ^ @x@ - x coordinate of rectangle to clear
 -> Int -- ^ @y@ - y coordinate of rectangle to clear
 -> Int -- ^ @width@ - width of rectangle to clear
 -> Int -- ^ @height@ - height of rectangle to clear
 -> IO ()
drawWindowClearAreaExpose self x y width height =
  (\(DrawWindow arg1) arg2 arg3 arg4 arg5 -> withForeignPtr arg1 $ \argPtr1 ->gdk_window_clear_area_e argPtr1 arg2 arg3 arg4 arg5)
{-# LINE 165 "./Graphics/UI/Gtk/Gdk/DrawWindow.chs" #-}
     (toDrawWindow self)
     (fromIntegral x)
     (fromIntegral y)
     (fromIntegral width)
     (fromIntegral height)

-- | Raises @DrawWindow@ to the top of the Z-order (stacking order), so that other
-- drawWindows with the same parent drawWindow appear below @DrawWindow@. This is true
-- whether or not the drawWindows are visible.
--
-- If @DrawWindow@ is a toplevel, the window manager may choose to deny the
-- request to move the drawWindow in the Z-order, 'drawWindowRaise' only requests the
-- restack, does not guarantee it.
--
drawWindowRaise :: DrawWindowClass self => self -> IO ()
drawWindowRaise self =
  (\(DrawWindow arg1) -> withForeignPtr arg1 $ \argPtr1 ->gdk_window_raise argPtr1)
{-# LINE 182 "./Graphics/UI/Gtk/Gdk/DrawWindow.chs" #-}
     (toDrawWindow self)

-- | Lowers @DrawWindow@ to the bottom of the Z-order (stacking order), so that
-- other windows with the same parent window appear above @DrawWindow@. This is
-- true whether or not the other windows are visible.
--
-- If @DrawWindow@ is a toplevel, the window manager may choose to deny the
-- request to move the drawWindow in the Z-order, 'drawWindowLower' only
-- requests the restack, does not guarantee it.
--
-- Note that a widget is raised automatically when it is mapped, thus you
-- need to call 'drawWindowLower' after
        -- 'Graphics.UI.Gtk.Abstract.Widget.widgetShow' if the window should
-- not appear above other windows.
--
drawWindowLower :: DrawWindowClass self => self -> IO ()
drawWindowLower self =
  (\(DrawWindow arg1) -> withForeignPtr arg1 $ \argPtr1 ->gdk_window_lower argPtr1)
{-# LINE 200 "./Graphics/UI/Gtk/Gdk/DrawWindow.chs" #-}
     (toDrawWindow self)

-- | Registers a drawWindow as a potential drop destination.
--
drawWindowRegisterDnd :: DrawWindowClass self => self -> IO ()
drawWindowRegisterDnd self =
  (\(DrawWindow arg1) -> withForeignPtr arg1 $ \argPtr1 ->gdk_window_register_dnd argPtr1)
{-# LINE 207 "./Graphics/UI/Gtk/Gdk/DrawWindow.chs" #-}
     (toDrawWindow self)

-- | A convenience wrapper around 'drawWindowBeginPaintRegion' which creates a
-- rectangular region for you.
--
-- * See 'drawWindowBeginPaintRegion' for details.
--
drawWindowBeginPaintRect :: DrawWindowClass self => self
 -> Rectangle -- ^ @rectangle@ - rectangle you intend to draw to
 -> IO ()
drawWindowBeginPaintRect self rectangle = with rectangle $ \rectPtr ->
  (\(DrawWindow arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gdk_window_begin_paint_rect argPtr1 arg2) (toDrawWindow self) (castPtr rectPtr)

-- | Indicate that you are beginning the process of redrawing @region@.
--
-- * A
-- backing store (offscreen buffer) large enough to contain @region@ will be
-- created. The backing store will be initialized with the background color or
-- background pixmap for @DrawWindow@. Then, all drawing operations performed on
-- @DrawWindow@ will be diverted to the backing store. When you call
-- 'drawWindowEndPaint', the backing store will be copied to @DrawWindow@, making it
-- visible onscreen. Only the part of @DrawWindow@ contained in @region@ will be
-- modified; that is, drawing operations are clipped to @region@.
--
-- The net result of all this is to remove flicker, because the user sees
-- the finished product appear all at once when you call 'drawWindowEndPaint'. If
-- you draw to @DrawWindow@ directly without calling 'drawWindowBeginPaintRegion', the
-- user may see flicker as individual drawing operations are performed in
-- sequence. The clipping and background-initializing features of
-- 'drawWindowBeginPaintRegion' are conveniences for the programmer, so you can
-- avoid doing that work yourself.
--
-- When using GTK+, the widget system automatically places calls to
-- 'drawWindowBeginPaintRegion' and 'drawWindowEndPaint' around emissions of the
-- @expose_event@ signal. That is, if you\'re writing an expose event handler,
-- you can assume that the exposed area in 'eventRegion' has already been
-- cleared to the window background, is already set as the clip region, and
-- already has a backing store. Therefore in most cases, application code need
-- not call 'drawWindowBeginPaintRegion'. (You can disable the automatic calls
-- around expose events on a widget-by-widget basis by calling
-- 'widgetSetDoubleBuffered'.)
--
-- If you call this function multiple times before calling the matching
-- 'drawWindowEndPaint', the backing stores are pushed onto a stack.
-- 'drawWindowEndPaint' copies the topmost backing store onscreen, subtracts the
-- topmost region from all other regions in the stack, and pops the stack. All
-- drawing operations affect only the topmost backing store in the stack. One
-- matching call to 'drawWindowEndPaint' is required for each call to
-- 'drawWindowBeginPaintRegion'.
--
drawWindowBeginPaintRegion :: DrawWindowClass self => self
 -> Region -- ^ @region@ - region you intend to draw to
 -> IO ()
drawWindowBeginPaintRegion self region =
  (\(DrawWindow arg1) (Region arg2) -> withForeignPtr arg1 $ \argPtr1 ->withForeignPtr arg2 $ \argPtr2 ->gdk_window_begin_paint_region argPtr1 argPtr2)
{-# LINE 262 "./Graphics/UI/Gtk/Gdk/DrawWindow.chs" #-}
     (toDrawWindow self)
     region

-- | Signal that drawing has finished.
--
-- * Indicates that the backing store created by the most recent call to
-- 'drawWindowBeginPaintRegion' should be copied onscreen and deleted, leaving the
-- next-most-recent backing store or no backing store at all as the active
-- paint region. See 'drawWindowBeginPaintRegion' for full details. It is an error
-- to call this function without a matching 'drawWindowBeginPaintRegion' first.
--
drawWindowEndPaint :: DrawWindowClass self => self -> IO ()
drawWindowEndPaint self =
  (\(DrawWindow arg1) -> withForeignPtr arg1 $ \argPtr1 ->gdk_window_end_paint argPtr1)
{-# LINE 276 "./Graphics/UI/Gtk/Gdk/DrawWindow.chs" #-}
     (toDrawWindow self)

-- | A convenience wrapper around 'drawWindowInvalidateRegion' which invalidates a
-- rectangular region. See 'drawWindowInvalidateRegion' for details.
--
drawWindowInvalidateRect :: DrawWindowClass self => self
 -> Rectangle -- ^ @rect@ - rectangle to invalidate
 -> Bool -- ^ @invalidateChildren@ - whether to also invalidate
                      -- child drawWindows
 -> IO ()
drawWindowInvalidateRect self rect invalidateChildren =
  with rect $ \rectPtr ->
  (\(DrawWindow arg1) arg2 arg3 -> withForeignPtr arg1 $ \argPtr1 ->gdk_window_invalidate_rect argPtr1 arg2 arg3)
{-# LINE 289 "./Graphics/UI/Gtk/Gdk/DrawWindow.chs" #-}
     (toDrawWindow self)
     (castPtr rectPtr)
     (fromBool invalidateChildren)

-- | Adds @region@ to the update area for @DrawWindow@. The update area is the
-- region that needs to be redrawn, or \"dirty region.\". During the
-- next idle period of the main look, an expose even for this region
-- will be created. An application would normally redraw
-- the contents of @DrawWindow@ in response to those expose events.
--
-- The @invalidateChildren@ parameter controls whether the region of each
-- child drawWindow that intersects @region@ will also be invalidated. If @False@,
-- then the update area for child drawWindows will remain unaffected.
--
drawWindowInvalidateRegion :: DrawWindowClass self => self
 -> Region -- ^ @region@ - a "Region"
 -> Bool -- ^ @invalidateChildren@ - @True@ to also invalidate child
                   -- drawWindows
 -> IO ()
drawWindowInvalidateRegion self region invalidateChildren =
  (\(DrawWindow arg1) (Region arg2) arg3 -> withForeignPtr arg1 $ \argPtr1 ->withForeignPtr arg2 $ \argPtr2 ->gdk_window_invalidate_region argPtr1 argPtr2 arg3)
{-# LINE 310 "./Graphics/UI/Gtk/Gdk/DrawWindow.chs" #-}
     (toDrawWindow self)
     region
     (fromBool invalidateChildren)

-- | Ask for the dirty region of this window.
--
-- * Transfers ownership of the update area from @DrawWindow@ to the caller of the
-- function. That is, after calling this function, @DrawWindow@ will no longer have
-- an invalid\/dirty region; the update area is removed from @DrawWindow@ and
-- handed to you. If this window has no update area, 'drawWindowGetUpdateArea' returns 'Nothing'.
--
drawWindowGetUpdateArea :: DrawWindowClass self => self
 -> IO (Maybe Region) -- ^ returns the update area for @DrawWindow@
drawWindowGetUpdateArea self = do
  reg <- (\(DrawWindow arg1) -> withForeignPtr arg1 $ \argPtr1 ->gdk_window_get_update_area argPtr1) (toDrawWindow self)
  if reg==nullPtr then return Nothing else liftM Just (makeNewRegion reg)

-- | Temporarily freezes a drawWindow such that it won\'t receive expose events.
-- * The drawWindow will begin receiving expose events again when
-- 'drawWindowThawUpdates'
-- is called. If 'drawWindowFreezeUpdates' has been called more than once,
-- 'drawWindowThawUpdates' must be called an equal number of times to begin
-- processing exposes.
--
drawWindowFreezeUpdates :: DrawWindowClass self => self -> IO ()
drawWindowFreezeUpdates self =
  (\(DrawWindow arg1) -> withForeignPtr arg1 $ \argPtr1 ->gdk_window_freeze_updates argPtr1)
{-# LINE 337 "./Graphics/UI/Gtk/Gdk/DrawWindow.chs" #-}
     (toDrawWindow self)

-- | Thaws a drawWindow frozen with 'drawWindowFreezeUpdates'.
--
drawWindowThawUpdates :: DrawWindowClass self => self -> IO ()
drawWindowThawUpdates self =
  (\(DrawWindow arg1) -> withForeignPtr arg1 $ \argPtr1 ->gdk_window_thaw_updates argPtr1)
{-# LINE 344 "./Graphics/UI/Gtk/Gdk/DrawWindow.chs" #-}
     (toDrawWindow self)

-- | Sends one or more expose events to @DrawWindow@.
--
-- * The areas in each expose
-- event will cover the entire update area for the window (see
-- 'drawWindowInvalidateRegion' for details). Normally Gtk calls
-- 'drawWindowProcessUpdates' on your behalf, so there's no need to call this
-- function unless you want to force expose events to be delivered immediately
-- and synchronously (vs. the usual case, where Gtk delivers them in an idle
-- handler). Occasionally this is useful to produce nicer scrolling behavior,
-- for example.
--
drawWindowProcessUpdates :: DrawWindowClass self => self
 -> Bool -- ^ @updateChildren@ - whether to also process updates for child
          -- drawWindows
 -> IO ()
drawWindowProcessUpdates self updateChildren =
  (\(DrawWindow arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gdk_window_process_updates argPtr1 arg2)
{-# LINE 363 "./Graphics/UI/Gtk/Gdk/DrawWindow.chs" #-}
     (toDrawWindow self)
     (fromBool updateChildren)


-- | Setting @acceptFocus@ to @False@ hints the desktop environment that the
-- window doesn\'t want to receive input focus.
--
-- On X, it is the responsibility of the drawWindow manager to interpret this
-- hint. ICCCM-compliant drawWindow manager usually respect it.
--
-- * Available since Gdk version 2.4
--
drawWindowSetAcceptFocus :: DrawWindowClass self => self
 -> Bool -- ^ @acceptFocus@ - @True@ if the drawWindow should receive input focus
 -> IO ()
drawWindowSetAcceptFocus self acceptFocus =
  (\(DrawWindow arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gdk_window_set_accept_focus argPtr1 arg2)
{-# LINE 380 "./Graphics/UI/Gtk/Gdk/DrawWindow.chs" #-}
     (toDrawWindow self)
     (fromBool acceptFocus)


-- | Applies a shape mask to window. Pixels in window corresponding to set
-- bits in the mask will be visible; pixels in window corresponding to
-- unset bits in the mask will be transparent. This gives a non-rectangular
-- window.
--
-- * If @mask@ is @Nothing@, the shape mask will be unset, and the x\/y parameters
-- are not used. The @mask@ must be a bitmap, that is, a 'Pixmap' of depth
-- one.
--
-- * On the X11 platform, this uses an X server extension which is widely
-- available on most common platforms, but not available on very old
-- X servers, and occasionally the implementation will be buggy.
-- On servers without the shape extension, this function will do nothing.
-- On the Win32 platform the functionality is always present.
--
-- * This function works on both toplevel and child windows.
--
drawWindowShapeCombineMask :: DrawWindowClass self => self
 -> Maybe Pixmap -- ^ @mask@ - region of drawWindow to be non-transparent
 -> Int -- ^ @offsetX@ - X position of @shapeRegion@ in @DrawWindow@
                   -- coordinates
 -> Int -- ^ @offsetY@ - Y position of @shapeRegion@ in @DrawWindow@
                   -- coordinates
 -> IO ()
drawWindowShapeCombineMask self (Just (Pixmap mask)) offsetX offsetY =
  withForeignPtr mask $ \maskPtr ->
  (\(DrawWindow arg1) arg2 arg3 arg4 -> withForeignPtr arg1 $ \argPtr1 ->gdk_window_shape_combine_mask argPtr1 arg2 arg3 arg4)
{-# LINE 411 "./Graphics/UI/Gtk/Gdk/DrawWindow.chs" #-}
     (toDrawWindow self)
     (castPtr maskPtr)
     (fromIntegral offsetX)
     (fromIntegral offsetY)
drawWindowShapeCombineMask self Nothing offsetX offsetY =
  (\(DrawWindow arg1) arg2 arg3 arg4 -> withForeignPtr arg1 $ \argPtr1 ->gdk_window_shape_combine_mask argPtr1 arg2 arg3 arg4)
{-# LINE 417 "./Graphics/UI/Gtk/Gdk/DrawWindow.chs" #-}
     (toDrawWindow self)
     nullPtr
     (fromIntegral offsetX)
     (fromIntegral offsetY)


-- | Makes pixels in @DrawWindow@ outside @shapeRegion@ transparent.
--
-- * Makes pixels in @DrawWindow@ outside @shapeRegion@ transparent, so that
-- the window may be nonrectangular.
--
-- If @shapeRegion@ is 'Nothing', the shape will be unset, so the whole
-- 'DrawWindow' will be opaque again. The parameters @offsetX@ and @offsetY@
-- are ignored if @shapeRegion@ is 'Nothing'.
--
-- On the X11 platform, this uses an X server extension which is widely
-- available on most common platforms, but not available on very old X servers,
-- and occasionally the implementation will be buggy. On servers without the
-- shape extension, this function will do nothing.
--
-- This function works on both toplevel and child drawWindows.
--
drawWindowShapeCombineRegion :: DrawWindowClass self => self
 -> Maybe Region -- ^ @shapeRegion@ - region of drawWindow to be non-transparent
 -> Int -- ^ @offsetX@ - X position of @shapeRegion@ in @DrawWindow@
                   -- coordinates
 -> Int -- ^ @offsetY@ - Y position of @shapeRegion@ in @DrawWindow@
                   -- coordinates
 -> IO ()
drawWindowShapeCombineRegion self (Just reg) offsetX offsetY =
  (\(DrawWindow arg1) (Region arg2) arg3 arg4 -> withForeignPtr arg1 $ \argPtr1 ->withForeignPtr arg2 $ \argPtr2 ->gdk_window_shape_combine_region argPtr1 argPtr2 arg3 arg4)
{-# LINE 448 "./Graphics/UI/Gtk/Gdk/DrawWindow.chs" #-}
     (toDrawWindow self)
     reg
     (fromIntegral offsetX)
     (fromIntegral offsetY)
drawWindowShapeCombineRegion self Nothing offsetX offsetY =
  (\(DrawWindow arg1) (Region arg2) arg3 arg4 -> withForeignPtr arg1 $ \argPtr1 ->withForeignPtr arg2 $ \argPtr2 ->gdk_window_shape_combine_region argPtr1 argPtr2 arg3 arg4)
{-# LINE 454 "./Graphics/UI/Gtk/Gdk/DrawWindow.chs" #-}
     (toDrawWindow self)
     (Region nullForeignPtr)
     (fromIntegral offsetX)
     (fromIntegral offsetY)

-- | Sets the shape mask of @DrawWindow@ to the union of shape masks for all
-- children of @DrawWindow@, ignoring the shape mask of @DrawWindow@ itself. Contrast
-- with 'drawWindowMergeChildShapes' which includes the shape mask of @DrawWindow@ in
-- the masks to be merged.
--
drawWindowSetChildShapes :: DrawWindowClass self => self -> IO ()
drawWindowSetChildShapes self =
  (\(DrawWindow arg1) -> withForeignPtr arg1 $ \argPtr1 ->gdk_window_set_child_shapes argPtr1)
{-# LINE 467 "./Graphics/UI/Gtk/Gdk/DrawWindow.chs" #-}
     (toDrawWindow self)

-- | Merges the shape masks for any child drawWindows into the shape mask for
-- @DrawWindow@. i.e. the union of all masks for @DrawWindow@ and its children will
-- become the new mask for @DrawWindow@. See 'drawWindowShapeCombineMask'.
--
-- This function is distinct from 'drawWindowSetChildShapes' because it includes
-- @DrawWindow@'s shape mask in the set of shapes to be merged.
--
drawWindowMergeChildShapes :: DrawWindowClass self => self -> IO ()
drawWindowMergeChildShapes self =
  (\(DrawWindow arg1) -> withForeignPtr arg1 $ \argPtr1 ->gdk_window_merge_child_shapes argPtr1)
{-# LINE 479 "./Graphics/UI/Gtk/Gdk/DrawWindow.chs" #-}
     (toDrawWindow self)

-- Superseded by 'drawWindowGetPointerPos', won't be removed.
-- Obtains the current pointer position and modifier state.
--
-- * The position is
-- given in coordinates relative to the given window.
--
-- * The return value is @Just (same, x, y, mod)@ where @same@ is @True@
-- if the passed in window is the window over which the mouse currently
-- resides.
--
-- * The return value is @Nothing@ if the mouse cursor is over a different
-- application.
--
drawWindowGetPointer :: DrawWindowClass self => self
 -> IO (Maybe (Bool, Int, Int, [Modifier]))
drawWindowGetPointer self =
  alloca $ \xPtr -> alloca $ \yPtr -> alloca $ \mPtr -> do
  winPtr <- (\(DrawWindow arg1) arg2 arg3 arg4 -> withForeignPtr arg1 $ \argPtr1 ->gdk_window_get_pointer argPtr1 arg2 arg3 arg4) (toDrawWindow self)
     xPtr yPtr mPtr
  if winPtr==nullPtr then return Nothing else do
  same <- withForeignPtr (unDrawWindow (toDrawWindow self)) $ \dPtr ->
          return (winPtr==dPtr)
  x <- peek xPtr
  y <- peek yPtr
  m <- peek mPtr
  return (Just (same, fromIntegral x, fromIntegral y,
                toFlags (fromIntegral m)))

-- | Obtains the current pointer position and modifier state.
--
-- * The position is
-- given in coordinates relative to the given window.
--
-- * The return value is @(Just win, x, y, mod)@ where @win@ is the
-- window over which the mouse currently resides and @mod@ denotes
-- the keyboard modifiers currently being depressed.
--
-- * The return value is @Nothing@ for the window if the mouse cursor is
-- not over a known window.
--
drawWindowGetPointerPos :: DrawWindowClass self => self
 -> IO (Maybe DrawWindow, Int, Int, [Modifier])
drawWindowGetPointerPos self =
  alloca $ \xPtr -> alloca $ \yPtr -> alloca $ \mPtr -> do
  winPtr <- (\(DrawWindow arg1) arg2 arg3 arg4 -> withForeignPtr arg1 $ \argPtr1 ->gdk_window_get_pointer argPtr1 arg2 arg3 arg4) (toDrawWindow self)
     xPtr yPtr mPtr
  x <- peek xPtr
  y <- peek yPtr
  m <- peek mPtr
  mWin <- if winPtr==nullPtr then return Nothing else liftM Just $
    makeNewGObject mkDrawWindow (return winPtr)
  return (mWin, fromIntegral x, fromIntegral y, toFlags (fromIntegral m))


-- | Obtains the position of a window in screen coordinates.
--
-- You can use this to help convert a position between screen coordinates and
-- local 'DrawWindow' relative coordinates.
--
drawWindowGetOrigin :: DrawWindow
 -> IO (Int, Int) -- ^ @(x, y)@
drawWindowGetOrigin self =
  alloca $ \xPtr ->
  alloca $ \yPtr -> do
  (\(DrawWindow arg1) arg2 arg3 -> withForeignPtr arg1 $ \argPtr1 ->gdk_window_get_origin argPtr1 arg2 arg3)
{-# LINE 546 "./Graphics/UI/Gtk/Gdk/DrawWindow.chs" #-}
    (toDrawWindow self)
    xPtr
    yPtr
  x <- peek xPtr
  y <- peek yPtr
  return (fromIntegral x, fromIntegral y)


-- | Get the handle to an exising window of the windowing system. The
-- passed-in handle is a reference to a native window, that is, an Xlib XID
-- for X windows and a HWND for Win32.
drawWindowForeignNew :: NativeWindowId -> IO (Maybe DrawWindow)
drawWindowForeignNew anid = maybeNull (wrapNewGObject mkDrawWindow) $
  liftM castPtr $ gdk_window_foreign_new (fromNativeWindowId anid)

-- | Obtains the root window (parent all other windows are inside) for the default display and screen.
drawWindowGetDefaultRootWindow ::
  IO DrawWindow -- ^ returns the default root window
drawWindowGetDefaultRootWindow =
  makeNewGObject mkDrawWindow $
  gdk_get_default_root_window
{-# LINE 567 "./Graphics/UI/Gtk/Gdk/DrawWindow.chs" #-}

foreign import ccall safe "gdk_window_get_state"
  gdk_window_get_state :: ((Ptr DrawWindow) -> (IO CInt))

foreign import ccall safe "gdk_window_scroll"
  gdk_window_scroll :: ((Ptr DrawWindow) -> (CInt -> (CInt -> (IO ()))))

foreign import ccall safe "gdk_window_clear"
  gdk_window_clear :: ((Ptr DrawWindow) -> (IO ()))

foreign import ccall safe "gdk_window_clear_area"
  gdk_window_clear_area :: ((Ptr DrawWindow) -> (CInt -> (CInt -> (CInt -> (CInt -> (IO ()))))))

foreign import ccall safe "gdk_window_clear_area_e"
  gdk_window_clear_area_e :: ((Ptr DrawWindow) -> (CInt -> (CInt -> (CInt -> (CInt -> (IO ()))))))

foreign import ccall safe "gdk_window_raise"
  gdk_window_raise :: ((Ptr DrawWindow) -> (IO ()))

foreign import ccall safe "gdk_window_lower"
  gdk_window_lower :: ((Ptr DrawWindow) -> (IO ()))

foreign import ccall safe "gdk_window_register_dnd"
  gdk_window_register_dnd :: ((Ptr DrawWindow) -> (IO ()))

foreign import ccall safe "gdk_window_begin_paint_rect"
  gdk_window_begin_paint_rect :: ((Ptr DrawWindow) -> ((Ptr ()) -> (IO ())))

foreign import ccall safe "gdk_window_begin_paint_region"
  gdk_window_begin_paint_region :: ((Ptr DrawWindow) -> ((Ptr Region) -> (IO ())))

foreign import ccall safe "gdk_window_end_paint"
  gdk_window_end_paint :: ((Ptr DrawWindow) -> (IO ()))

foreign import ccall safe "gdk_window_invalidate_rect"
  gdk_window_invalidate_rect :: ((Ptr DrawWindow) -> ((Ptr ()) -> (CInt -> (IO ()))))

foreign import ccall safe "gdk_window_invalidate_region"
  gdk_window_invalidate_region :: ((Ptr DrawWindow) -> ((Ptr Region) -> (CInt -> (IO ()))))

foreign import ccall safe "gdk_window_get_update_area"
  gdk_window_get_update_area :: ((Ptr DrawWindow) -> (IO (Ptr Region)))

foreign import ccall safe "gdk_window_freeze_updates"
  gdk_window_freeze_updates :: ((Ptr DrawWindow) -> (IO ()))

foreign import ccall safe "gdk_window_thaw_updates"
  gdk_window_thaw_updates :: ((Ptr DrawWindow) -> (IO ()))

foreign import ccall safe "gdk_window_process_updates"
  gdk_window_process_updates :: ((Ptr DrawWindow) -> (CInt -> (IO ())))

foreign import ccall safe "gdk_window_set_accept_focus"
  gdk_window_set_accept_focus :: ((Ptr DrawWindow) -> (CInt -> (IO ())))

foreign import ccall safe "gdk_window_shape_combine_mask"
  gdk_window_shape_combine_mask :: ((Ptr DrawWindow) -> ((Ptr ()) -> (CInt -> (CInt -> (IO ())))))

foreign import ccall safe "gdk_window_shape_combine_region"
  gdk_window_shape_combine_region :: ((Ptr DrawWindow) -> ((Ptr Region) -> (CInt -> (CInt -> (IO ())))))

foreign import ccall safe "gdk_window_set_child_shapes"
  gdk_window_set_child_shapes :: ((Ptr DrawWindow) -> (IO ()))

foreign import ccall safe "gdk_window_merge_child_shapes"
  gdk_window_merge_child_shapes :: ((Ptr DrawWindow) -> (IO ()))

foreign import ccall safe "gdk_window_get_pointer"
  gdk_window_get_pointer :: ((Ptr DrawWindow) -> ((Ptr CInt) -> ((Ptr CInt) -> ((Ptr CInt) -> (IO (Ptr DrawWindow))))))

foreign import ccall safe "gdk_window_get_origin"
  gdk_window_get_origin :: ((Ptr DrawWindow) -> ((Ptr CInt) -> ((Ptr CInt) -> (IO CInt))))

foreign import ccall safe "gdk_window_foreign_new"
  gdk_window_foreign_new :: (CUInt -> (IO (Ptr DrawWindow)))

foreign import ccall safe "gdk_get_default_root_window"
  gdk_get_default_root_window :: (IO (Ptr DrawWindow))