{-# LINE 2 "./Graphics/UI/Gtk/Windows/Window.chs" #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LINE 3 "./Graphics/UI/Gtk/Windows/Window.chs" #-}
module Graphics.UI.Gtk.Windows.Window (
  Window,
  WindowClass,
  castToWindow, gTypeWindow,
  toWindow,
  WindowType(..),
  WindowEdge(..),
  WindowTypeHint(..),
  Gravity(..),
  windowNew,
  windowNewPopup,
  windowActivateFocus,
  windowActivateDefault,
  windowSetDefaultSize,
  windowGetDefaultSize,
  windowSetPosition,
  WindowPosition(..),
  windowIsActive,
  windowHasToplevelFocus,
  windowListToplevels,
  windowSetDefault,
  windowGetDefaultWidget,
  windowAddMnemonic,
  windowRemoveMnemonic,
  windowMnemonicActivate,
  windowActivateKey,
  windowPropagateKeyEvent,
  windowPresent,
  windowDeiconify,
  windowIconify,
  windowMaximize,
  windowUnmaximize,
  windowFullscreen,
  windowUnfullscreen,
  windowSetKeepAbove,
  windowSetKeepBelow,
  windowSetStartupId,
  windowStick,
  windowUnstick,
  windowAddAccelGroup,
  windowRemoveAccelGroup,
  windowSetDefaultIconList,
  windowGetDefaultIconList,
  windowSetDefaultIcon,
  windowSetDefaultIconFromFile,
  windowSetDefaultIconName,
  windowGetDefaultIconName,
  windowSetGravity,
  windowGetGravity,
  windowSetScreen,
  windowGetScreen,
  windowBeginResizeDrag,
  windowBeginMoveDrag,
  windowSetTypeHint,
  windowGetTypeHint,
  windowGetIcon,
  windowGetPosition,
  windowGetSize,
  windowMove,
  windowParseGeometry,
  windowReshowWithInitialSize,
  windowResize,
  windowSetIconFromFile,
  windowSetAutoStartupNotification,
  windowPresentWithTime,
  windowSetGeometryHints,
  windowGetGroup,
  windowGetWindowType,
  windowTitle,
  windowType,
  windowAllowShrink,
  windowAllowGrow,
  windowResizable,
  windowHasResizeGrip,
  windowModal,
  windowOpacity,
  windowRole,
  windowStartupId,
  windowWindowPosition,
  windowDefaultWidth,
  windowDefaultHeight,
  windowDeletable,
  windowDestroyWithParent,
  windowIcon,
  windowIconName,
  windowScreen,
  windowTypeHint,
  windowSkipTaskbarHint,
  windowSkipPagerHint,
  windowUrgencyHint,
  windowAcceptFocus,
  windowFocusOnMap,
  windowDecorated,
  windowGravity,
  windowToplevelFocus,
  windowTransientFor,
  windowFocus,
  windowIconList,
  windowMnemonicModifier,
  windowMnemonicVisible,
  frameEvent,
  keysChanged,
  setFocus,
{-# LINE 278 "./Graphics/UI/Gtk/Windows/Window.chs" #-}
  ) where
import Control.Monad (liftM)
import System.Glib.FFI
import System.Glib.UTFString
import System.Glib.Flags
import System.Glib.GError
import System.Glib.Attributes
import System.Glib.Properties
import System.Glib.GList (fromGList, withGList)
import Graphics.UI.Gtk.Abstract.Object (makeNewObject)
import Graphics.UI.Gtk.General.Enums (WindowType(..), WindowPosition(..))
import Graphics.UI.Gtk.Types
{-# LINE 295 "./Graphics/UI/Gtk/Windows/Window.chs" #-}
import Graphics.UI.Gtk.Signals
{-# LINE 296 "./Graphics/UI/Gtk/Windows/Window.chs" #-}
import Graphics.UI.Gtk.Gdk.Enums (Modifier(..))
import Graphics.UI.Gtk.Gdk.Keys (KeyVal)
import Graphics.UI.Gtk.Gdk.EventM (EventM, EAny, EKey, MouseButton, TimeStamp)
import Control.Monad.Reader ( runReaderT, ask )
import Control.Monad.Trans ( liftIO )
import Graphics.UI.Gtk.Gdk.Enums (WindowEdge(..), WindowTypeHint(..),
                                        Gravity(..))
{-# LINE 305 "./Graphics/UI/Gtk/Windows/Window.chs" #-}
windowNew :: IO Window
windowNew =
  makeNewObject mkWindow $
  liftM (castPtr :: Ptr Widget -> Ptr Window) $
  gtk_window_new
{-# LINE 316 "./Graphics/UI/Gtk/Windows/Window.chs" #-}
    ((fromIntegral . fromEnum) WindowToplevel)
windowNewPopup :: IO Window
windowNewPopup =
  makeNewObject mkWindow $
  liftM (castPtr :: Ptr Widget -> Ptr Window) $
  gtk_window_new
{-# LINE 325 "./Graphics/UI/Gtk/Windows/Window.chs" #-}
    ((fromIntegral . fromEnum) WindowPopup)
windowSetTitle :: (WindowClass self, GlibString string) => self -> string -> IO ()
windowSetTitle self title =
  withUTFString title $ \titlePtr ->
  (\(Window arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_window_set_title argPtr1 arg2)
{-# LINE 341 "./Graphics/UI/Gtk/Windows/Window.chs" #-}
    (toWindow self)
    titlePtr
windowGetTitle :: (WindowClass self, GlibString string) => self -> IO string
windowGetTitle self =
  (\(Window arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_window_get_title argPtr1)
{-# LINE 349 "./Graphics/UI/Gtk/Windows/Window.chs" #-}
    (toWindow self)
  >>= \strPtr -> if strPtr == nullPtr
                   then return ""
                   else peekUTFString strPtr
windowSetResizable :: WindowClass self => self -> Bool -> IO ()
windowSetResizable self resizable =
  (\(Window arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_window_set_resizable argPtr1 arg2)
{-# LINE 360 "./Graphics/UI/Gtk/Windows/Window.chs" #-}
    (toWindow self)
    (fromBool resizable)
windowGetResizable :: WindowClass self => self
 -> IO Bool 
windowGetResizable self =
  liftM toBool $
  (\(Window arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_window_get_resizable argPtr1)
{-# LINE 370 "./Graphics/UI/Gtk/Windows/Window.chs" #-}
    (toWindow self)
windowSetHasResizeGrip :: WindowClass self => self -> Bool -> IO ()
windowSetHasResizeGrip self setting =
  (\(Window arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_window_set_has_resize_grip argPtr1 arg2)
{-# LINE 378 "./Graphics/UI/Gtk/Windows/Window.chs" #-}
    (toWindow self)
    (fromBool setting)
windowGetHasResizeGrip :: WindowClass self => self -> IO Bool
windowGetHasResizeGrip self =
  liftM toBool $
  (\(Window arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_window_get_has_resize_grip argPtr1)
{-# LINE 387 "./Graphics/UI/Gtk/Windows/Window.chs" #-}
    (toWindow self)
windowActivateFocus :: WindowClass self => self
 -> IO Bool 
windowActivateFocus self =
  liftM toBool $
  (\(Window arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_window_activate_focus argPtr1)
{-# LINE 397 "./Graphics/UI/Gtk/Windows/Window.chs" #-}
    (toWindow self)
windowActivateDefault :: WindowClass self => self
 -> IO Bool 
windowActivateDefault self =
  liftM toBool $
  (\(Window arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_window_activate_default argPtr1)
{-# LINE 409 "./Graphics/UI/Gtk/Windows/Window.chs" #-}
    (toWindow self)
{-# LINE 430 "./Graphics/UI/Gtk/Windows/Window.chs" #-}
windowSetModal :: WindowClass self => self
 -> Bool 
 -> IO ()
windowSetModal self modal =
  (\(Window arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_window_set_modal argPtr1 arg2)
{-# LINE 441 "./Graphics/UI/Gtk/Windows/Window.chs" #-}
    (toWindow self)
    (fromBool modal)
windowGetModal :: WindowClass self => self
 -> IO Bool 
            
windowGetModal self =
  liftM toBool $
  (\(Window arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_window_get_modal argPtr1)
{-# LINE 452 "./Graphics/UI/Gtk/Windows/Window.chs" #-}
    (toWindow self)
windowSetDefaultSize :: WindowClass self => self
 -> Int 
 -> Int 
 -> IO ()
windowSetDefaultSize self height width =
  (\(Window arg1) arg2 arg3 -> withForeignPtr arg1 $ \argPtr1 ->gtk_window_set_default_size argPtr1 arg2 arg3)
{-# LINE 488 "./Graphics/UI/Gtk/Windows/Window.chs" #-}
    (toWindow self)
    (fromIntegral height)
    (fromIntegral width)
windowAddMnemonic :: (WindowClass self, WidgetClass widget) => self
 -> KeyVal 
 -> widget 
 -> IO ()
windowAddMnemonic self keyval target =
  (\(Window arg1) arg2 (Widget arg3) -> withForeignPtr arg1 $ \argPtr1 ->withForeignPtr arg3 $ \argPtr3 ->gtk_window_add_mnemonic argPtr1 arg2 argPtr3)
{-# LINE 500 "./Graphics/UI/Gtk/Windows/Window.chs" #-}
    (toWindow self)
    (fromIntegral keyval)
    (toWidget target)
windowRemoveMnemonic :: (WindowClass self, WidgetClass widget) => self
 -> KeyVal 
 -> widget 
 -> IO ()
windowRemoveMnemonic self keyval target =
  (\(Window arg1) arg2 (Widget arg3) -> withForeignPtr arg1 $ \argPtr1 ->withForeignPtr arg3 $ \argPtr3 ->gtk_window_remove_mnemonic argPtr1 arg2 argPtr3)
{-# LINE 512 "./Graphics/UI/Gtk/Windows/Window.chs" #-}
    (toWindow self)
    (fromIntegral keyval)
    (toWidget target)
windowMnemonicActivate :: WindowClass self => self
 -> KeyVal 
 -> [Modifier] 
 -> IO Bool 
windowMnemonicActivate self keyval modifier = liftM toBool $
  (\(Window arg1) arg2 arg3 -> withForeignPtr arg1 $ \argPtr1 ->gtk_window_mnemonic_activate argPtr1 arg2 arg3)
{-# LINE 523 "./Graphics/UI/Gtk/Windows/Window.chs" #-}
    (toWindow self)
    (fromIntegral keyval)
    (fromIntegral (fromFlags modifier))
windowSetMnemonicModifier :: WindowClass self => self
 -> [Modifier] 
 -> IO ()
windowSetMnemonicModifier self modifier =
  (\(Window arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_window_set_mnemonic_modifier argPtr1 arg2)
{-# LINE 533 "./Graphics/UI/Gtk/Windows/Window.chs" #-}
    (toWindow self)
    (fromIntegral (fromFlags modifier))
windowGetMnemonicModifier :: WindowClass self => self
 -> IO [Modifier] 
windowGetMnemonicModifier self = liftM (toFlags . fromIntegral) $
  (\(Window arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_window_get_mnemonic_modifier argPtr1)
{-# LINE 541 "./Graphics/UI/Gtk/Windows/Window.chs" #-}
    (toWindow self)
windowActivateKey :: WindowClass self => self -> EventM EKey Bool
  
windowActivateKey self = do
  ptr <- ask
  liftIO $ liftM toBool $
    (\(Window arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_window_activate_key argPtr1 arg2)
{-# LINE 553 "./Graphics/UI/Gtk/Windows/Window.chs" #-}
      (toWindow self)
      (castPtr ptr)
windowPropagateKeyEvent :: WindowClass self => self
  -> EventM EKey Bool
  
windowPropagateKeyEvent self = do
  ptr <- ask
  liftIO $ liftM toBool $
    (\(Window arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_window_propagate_key_event argPtr1 arg2)
{-# LINE 567 "./Graphics/UI/Gtk/Windows/Window.chs" #-}
      (toWindow self)
      (castPtr ptr)
windowGetDefaultSize :: WindowClass self => self
 -> IO (Int, Int) 
windowGetDefaultSize self =
  alloca $ \widthPtr ->
  alloca $ \heightPtr -> do
  (\(Window arg1) arg2 arg3 -> withForeignPtr arg1 $ \argPtr1 ->gtk_window_get_default_size argPtr1 arg2 arg3)
{-# LINE 580 "./Graphics/UI/Gtk/Windows/Window.chs" #-}
    (toWindow self)
    widthPtr
    heightPtr
  width <- peek widthPtr
  height <- peek heightPtr
  return (fromIntegral width, fromIntegral height)
windowSetPosition :: WindowClass self => self -> WindowPosition -> IO ()
windowSetPosition self position =
  (\(Window arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_window_set_position argPtr1 arg2)
{-# LINE 594 "./Graphics/UI/Gtk/Windows/Window.chs" #-}
    (toWindow self)
    ((fromIntegral . fromEnum) position)
windowSetTransientFor :: (WindowClass self, WindowClass parent) => self
 -> parent 
 -> IO ()
windowSetTransientFor self parent =
  (\(Window arg1) (Window arg2) -> withForeignPtr arg1 $ \argPtr1 ->withForeignPtr arg2 $ \argPtr2 ->gtk_window_set_transient_for argPtr1 argPtr2)
{-# LINE 615 "./Graphics/UI/Gtk/Windows/Window.chs" #-}
    (toWindow self)
    (toWindow parent)
windowGetTransientFor :: WindowClass self => self
 -> IO (Maybe Window) 
                      
windowGetTransientFor self =
  maybeNull (makeNewObject mkWindow) $
  (\(Window arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_window_get_transient_for argPtr1)
{-# LINE 627 "./Graphics/UI/Gtk/Windows/Window.chs" #-}
    (toWindow self)
windowSetDestroyWithParent :: WindowClass self => self -> Bool -> IO ()
windowSetDestroyWithParent self setting =
  (\(Window arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_window_set_destroy_with_parent argPtr1 arg2)
{-# LINE 637 "./Graphics/UI/Gtk/Windows/Window.chs" #-}
    (toWindow self)
    (fromBool setting)
windowGetDestroyWithParent :: WindowClass self => self
 -> IO Bool 
            
windowGetDestroyWithParent self =
  liftM toBool $
  (\(Window arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_window_get_destroy_with_parent argPtr1)
{-# LINE 649 "./Graphics/UI/Gtk/Windows/Window.chs" #-}
    (toWindow self)
windowIsActive :: WindowClass self => self
 -> IO Bool 
            
windowIsActive self =
  liftM toBool $
  (\(Window arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_window_is_active argPtr1)
{-# LINE 667 "./Graphics/UI/Gtk/Windows/Window.chs" #-}
    (toWindow self)
windowHasToplevelFocus :: WindowClass self => self
 -> IO Bool 
windowHasToplevelFocus self =
  liftM toBool $
  (\(Window arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_window_has_toplevel_focus argPtr1)
{-# LINE 680 "./Graphics/UI/Gtk/Windows/Window.chs" #-}
    (toWindow self)
windowListToplevels :: IO [Window]
windowListToplevels = do
  glistPtr <- gtk_window_list_toplevels
{-# LINE 688 "./Graphics/UI/Gtk/Windows/Window.chs" #-}
  winPtrs <- fromGList glistPtr
  mapM (\ptr -> makeNewGObject mkWindow (return ptr)) winPtrs
windowGetFocus :: WindowClass self => self -> IO (Maybe Widget)
windowGetFocus self =
  maybeNull (makeNewObject mkWidget) $
  (\(Window arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_window_get_focus argPtr1)
{-# LINE 700 "./Graphics/UI/Gtk/Windows/Window.chs" #-}
    (toWindow self)
windowSetFocus :: (WindowClass self, WidgetClass widget) => self
  -> Maybe widget
  -> IO ()
windowSetFocus self focus =
  (\(Window arg1) (Widget arg2) -> withForeignPtr arg1 $ \argPtr1 ->withForeignPtr arg2 $ \argPtr2 ->gtk_window_set_focus argPtr1 argPtr2)
{-# LINE 713 "./Graphics/UI/Gtk/Windows/Window.chs" #-}
    (toWindow self)
    (maybe (Widget nullForeignPtr) toWidget focus)
windowGetDefaultWidget :: WindowClass self => self
 -> IO (Maybe Widget)
windowGetDefaultWidget self =
  maybeNull (makeNewObject mkWidget) $
  (\(Window arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_window_get_default_widget argPtr1)
{-# LINE 726 "./Graphics/UI/Gtk/Windows/Window.chs" #-}
    (toWindow self)
windowSetDefault :: (WindowClass self, WidgetClass widget) => self
  -> Maybe widget
  -> IO ()
windowSetDefault self defaultWidget =
  (\(Window arg1) (Widget arg2) -> withForeignPtr arg1 $ \argPtr1 ->withForeignPtr arg2 $ \argPtr2 ->gtk_window_set_focus argPtr1 argPtr2)
{-# LINE 741 "./Graphics/UI/Gtk/Windows/Window.chs" #-}
    (toWindow self)
    (maybe (Widget nullForeignPtr) toWidget defaultWidget)
windowPresent :: WindowClass self => self -> IO ()
windowPresent self =
  (\(Window arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_window_present argPtr1)
{-# LINE 762 "./Graphics/UI/Gtk/Windows/Window.chs" #-}
    (toWindow self)
windowDeiconify :: WindowClass self => self -> IO ()
windowDeiconify self =
  (\(Window arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_window_deiconify argPtr1)
{-# LINE 775 "./Graphics/UI/Gtk/Windows/Window.chs" #-}
    (toWindow self)
windowIconify :: WindowClass self => self -> IO ()
windowIconify self =
  (\(Window arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_window_iconify argPtr1)
{-# LINE 793 "./Graphics/UI/Gtk/Windows/Window.chs" #-}
    (toWindow self)
windowMaximize :: WindowClass self => self -> IO ()
windowMaximize self =
  (\(Window arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_window_maximize argPtr1)
{-# LINE 810 "./Graphics/UI/Gtk/Windows/Window.chs" #-}
    (toWindow self)
windowUnmaximize :: WindowClass self => self -> IO ()
windowUnmaximize self =
  (\(Window arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_window_unmaximize argPtr1)
{-# LINE 824 "./Graphics/UI/Gtk/Windows/Window.chs" #-}
    (toWindow self)
windowFullscreen :: WindowClass self => self -> IO ()
windowFullscreen self =
  (\(Window arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_window_fullscreen argPtr1)
{-# LINE 842 "./Graphics/UI/Gtk/Windows/Window.chs" #-}
    (toWindow self)
windowUnfullscreen :: WindowClass self => self -> IO ()
windowUnfullscreen self =
  (\(Window arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_window_unfullscreen argPtr1)
{-# LINE 859 "./Graphics/UI/Gtk/Windows/Window.chs" #-}
    (toWindow self)
windowSetKeepAbove :: WindowClass self => self
 -> Bool 
 -> IO ()
windowSetKeepAbove self setting =
  (\(Window arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_window_set_keep_above argPtr1 arg2)
{-# LINE 885 "./Graphics/UI/Gtk/Windows/Window.chs" #-}
    (toWindow self)
    (fromBool setting)
windowSetKeepBelow :: WindowClass self => self
 -> Bool 
 -> IO ()
windowSetKeepBelow self setting =
  (\(Window arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_window_set_keep_below argPtr1 arg2)
{-# LINE 911 "./Graphics/UI/Gtk/Windows/Window.chs" #-}
    (toWindow self)
    (fromBool setting)
windowSetSkipTaskbarHint :: WindowClass self => self
 -> Bool 
          
 -> IO ()
windowSetSkipTaskbarHint self setting =
  (\(Window arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_window_set_skip_taskbar_hint argPtr1 arg2)
{-# LINE 926 "./Graphics/UI/Gtk/Windows/Window.chs" #-}
    (toWindow self)
    (fromBool setting)
windowGetSkipTaskbarHint :: WindowClass self => self
 -> IO Bool 
windowGetSkipTaskbarHint self =
  liftM toBool $
  (\(Window arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_window_get_skip_taskbar_hint argPtr1)
{-# LINE 938 "./Graphics/UI/Gtk/Windows/Window.chs" #-}
    (toWindow self)
windowSetSkipPagerHint :: WindowClass self => self
 -> Bool 
          
 -> IO ()
windowSetSkipPagerHint self setting =
  (\(Window arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_window_set_skip_pager_hint argPtr1 arg2)
{-# LINE 953 "./Graphics/UI/Gtk/Windows/Window.chs" #-}
    (toWindow self)
    (fromBool setting)
windowGetSkipPagerHint :: WindowClass self => self
 -> IO Bool 
windowGetSkipPagerHint self =
  liftM toBool $
  (\(Window arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_window_get_skip_pager_hint argPtr1)
{-# LINE 965 "./Graphics/UI/Gtk/Windows/Window.chs" #-}
    (toWindow self)
windowSetAcceptFocus :: WindowClass self => self
 -> Bool 
 -> IO ()
windowSetAcceptFocus self setting =
  (\(Window arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_window_set_accept_focus argPtr1 arg2)
{-# LINE 979 "./Graphics/UI/Gtk/Windows/Window.chs" #-}
    (toWindow self)
    (fromBool setting)
windowGetAcceptFocus :: WindowClass self => self
 -> IO Bool 
windowGetAcceptFocus self =
  liftM toBool $
  (\(Window arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_window_get_accept_focus argPtr1)
{-# LINE 991 "./Graphics/UI/Gtk/Windows/Window.chs" #-}
    (toWindow self)
windowSetFocusOnMap :: WindowClass self => self
 -> Bool 
          
 -> IO ()
windowSetFocusOnMap self setting =
  (\(Window arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_window_set_focus_on_map argPtr1 arg2)
{-# LINE 1006 "./Graphics/UI/Gtk/Windows/Window.chs" #-}
    (toWindow self)
    (fromBool setting)
windowGetFocusOnMap :: WindowClass self => self
 -> IO Bool 
            
windowGetFocusOnMap self =
  liftM toBool $
  (\(Window arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_window_get_focus_on_map argPtr1)
{-# LINE 1019 "./Graphics/UI/Gtk/Windows/Window.chs" #-}
    (toWindow self)
windowSetStartupId :: (WindowClass self, GlibString string) => self
 -> string
 -> IO ()
windowSetStartupId self startupId =
  withUTFString startupId $ \idPtr ->
  (\(Window arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_window_set_startup_id argPtr1 arg2)
{-# LINE 1037 "./Graphics/UI/Gtk/Windows/Window.chs" #-}
    (toWindow self)
    idPtr
windowSetDecorated :: WindowClass self => self -> Bool -> IO ()
windowSetDecorated self setting =
  (\(Window arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_window_set_decorated argPtr1 arg2)
{-# LINE 1055 "./Graphics/UI/Gtk/Windows/Window.chs" #-}
    (toWindow self)
    (fromBool setting)
windowGetDecorated :: WindowClass self => self
 -> IO Bool 
windowGetDecorated self =
  liftM toBool $
  (\(Window arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_window_get_decorated argPtr1)
{-# LINE 1066 "./Graphics/UI/Gtk/Windows/Window.chs" #-}
    (toWindow self)
{-# LINE 1214 "./Graphics/UI/Gtk/Windows/Window.chs" #-}
windowStick :: WindowClass self => self -> IO ()
windowStick self =
  (\(Window arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_window_stick argPtr1)
{-# LINE 1229 "./Graphics/UI/Gtk/Windows/Window.chs" #-}
    (toWindow self)
windowUnstick :: WindowClass self => self -> IO ()
windowUnstick self =
  (\(Window arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_window_unstick argPtr1)
{-# LINE 1243 "./Graphics/UI/Gtk/Windows/Window.chs" #-}
    (toWindow self)
windowAddAccelGroup :: WindowClass self => self
 -> AccelGroup 
 -> IO ()
windowAddAccelGroup self accelGroup =
  (\(Window arg1) (AccelGroup arg2) -> withForeignPtr arg1 $ \argPtr1 ->withForeignPtr arg2 $ \argPtr2 ->gtk_window_add_accel_group argPtr1 argPtr2)
{-# LINE 1254 "./Graphics/UI/Gtk/Windows/Window.chs" #-}
    (toWindow self)
    accelGroup
windowRemoveAccelGroup :: WindowClass self => self
 -> AccelGroup 
 -> IO ()
windowRemoveAccelGroup self accelGroup =
  (\(Window arg1) (AccelGroup arg2) -> withForeignPtr arg1 $ \argPtr1 ->withForeignPtr arg2 $ \argPtr2 ->gtk_window_remove_accel_group argPtr1 argPtr2)
{-# LINE 1264 "./Graphics/UI/Gtk/Windows/Window.chs" #-}
    (toWindow self)
    accelGroup
windowSetIcon :: WindowClass self => self
 -> Maybe Pixbuf 
 -> IO ()
windowSetIcon self Nothing =
  (\(Window arg1) (Pixbuf arg2) -> withForeignPtr arg1 $ \argPtr1 ->withForeignPtr arg2 $ \argPtr2 ->gtk_window_set_icon argPtr1 argPtr2)
{-# LINE 1291 "./Graphics/UI/Gtk/Windows/Window.chs" #-}
    (toWindow self)
    (Pixbuf nullForeignPtr)
windowSetIcon self (Just icon) =
  (\(Window arg1) (Pixbuf arg2) -> withForeignPtr arg1 $ \argPtr1 ->withForeignPtr arg2 $ \argPtr2 ->gtk_window_set_icon argPtr1 argPtr2)
{-# LINE 1295 "./Graphics/UI/Gtk/Windows/Window.chs" #-}
    (toWindow self)
    icon
windowGetIcon :: WindowClass self => self
 -> IO (Maybe Pixbuf) 
windowGetIcon self =
  maybeNull (makeNewGObject mkPixbuf) $
  (\(Window arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_window_get_icon argPtr1)
{-# LINE 1306 "./Graphics/UI/Gtk/Windows/Window.chs" #-}
    (toWindow self)
windowSetIconList :: WindowClass self => self
 -> [Pixbuf]
 -> IO ()
windowSetIconList self list =
  withForeignPtrs (map unPixbuf list) $ \ptrList ->
  withGList ptrList $ \glist ->
  (\(Window arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_window_set_icon_list argPtr1 arg2)
{-# LINE 1332 "./Graphics/UI/Gtk/Windows/Window.chs" #-}
     (toWindow self)
     glist
windowGetIconList :: WindowClass self => self
 -> IO [Pixbuf]
windowGetIconList self = do
  glist <- (\(Window arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_window_get_icon_list argPtr1) (toWindow self)
  ptrList <- fromGList glist
  mapM (makeNewGObject mkPixbuf . return) ptrList
windowSetDefaultIconList :: [Pixbuf] -> IO ()
windowSetDefaultIconList list =
  withForeignPtrs (map unPixbuf list) $ \ptrList ->
  withGList ptrList $ \glist ->
  gtk_window_set_default_icon_list glist
windowGetDefaultIconList :: IO [Pixbuf]
windowGetDefaultIconList = do
  glist <- gtk_window_get_default_icon_list
{-# LINE 1360 "./Graphics/UI/Gtk/Windows/Window.chs" #-}
  ptrList <- fromGList glist
  mapM (makeNewGObject mkPixbuf . return) ptrList
{-# LINE 1398 "./Graphics/UI/Gtk/Windows/Window.chs" #-}
windowSetDefaultIconName :: GlibString string
 => string 
 -> IO ()
windowSetDefaultIconName name =
  withUTFString name $ \namePtr ->
  gtk_window_set_default_icon_name
{-# LINE 1410 "./Graphics/UI/Gtk/Windows/Window.chs" #-}
    namePtr
windowSetDefaultIcon :: Maybe Pixbuf -> IO ()
windowSetDefaultIcon (Just icon) =
  (\(Pixbuf arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_window_set_default_icon argPtr1) icon
windowSetDefaultIcon Nothing =
  (\(Pixbuf arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_window_set_default_icon argPtr1) (Pixbuf nullForeignPtr)
windowSetDefaultIconFromFile :: GlibString string
 => string 
 -> IO Bool 
windowSetDefaultIconFromFile filename =
  liftM toBool $
  propagateGError $ \errPtr ->
  withUTFString filename $ \filenamePtr ->
  gtk_window_set_default_icon_from_file
{-# LINE 1440 "./Graphics/UI/Gtk/Windows/Window.chs" #-}
    filenamePtr
    errPtr
windowGetDefaultIconName :: GlibString string
 => IO string 
windowGetDefaultIconName =
  gtk_window_get_default_icon_name
{-# LINE 1454 "./Graphics/UI/Gtk/Windows/Window.chs" #-}
  >>= peekUTFString
windowSetScreen :: WindowClass self => self
 -> Screen 
 -> IO ()
windowSetScreen self screen =
  (\(Window arg1) (Screen arg2) -> withForeignPtr arg1 $ \argPtr1 ->withForeignPtr arg2 $ \argPtr2 ->gtk_window_set_screen argPtr1 argPtr2)
{-# LINE 1468 "./Graphics/UI/Gtk/Windows/Window.chs" #-}
    (toWindow self)
    screen
windowGetScreen :: WindowClass self => self
 -> IO Screen 
windowGetScreen self =
  makeNewGObject mkScreen $
  (\(Window arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_window_get_screen argPtr1)
{-# LINE 1480 "./Graphics/UI/Gtk/Windows/Window.chs" #-}
    (toWindow self)
windowSetIconFromFile :: (WindowClass self, GlibFilePath fp) => self
 -> fp 
 -> IO ()
windowSetIconFromFile self filename =
  propagateGError $ \errPtr ->
  withUTFFilePath filename $ \filenamePtr -> do
  (\(Window arg1) arg2 arg3 -> withForeignPtr arg1 $ \argPtr1 ->gtk_window_set_icon_from_file argPtr1 arg2 arg3)
{-# LINE 1501 "./Graphics/UI/Gtk/Windows/Window.chs" #-}
    (toWindow self)
    filenamePtr
    errPtr
  return ()
windowSetAutoStartupNotification ::
    Bool 
 -> IO ()
windowSetAutoStartupNotification setting =
  gtk_window_set_auto_startup_notification
{-# LINE 1524 "./Graphics/UI/Gtk/Windows/Window.chs" #-}
    (fromBool setting)
windowSetGravity :: WindowClass self => self
 -> Gravity 
 -> IO ()
windowSetGravity self gravity =
  (\(Window arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_window_set_gravity argPtr1 arg2)
{-# LINE 1538 "./Graphics/UI/Gtk/Windows/Window.chs" #-}
    (toWindow self)
    ((fromIntegral . fromEnum) gravity)
windowGetGravity :: WindowClass self => self
 -> IO Gravity 
windowGetGravity self =
  liftM (toEnum . fromIntegral) $
  (\(Window arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_window_get_gravity argPtr1)
{-# LINE 1548 "./Graphics/UI/Gtk/Windows/Window.chs" #-}
    (toWindow self)
windowMove :: WindowClass self => self
 -> Int 
 -> Int 
 -> IO ()
windowMove self x y =
  (\(Window arg1) arg2 arg3 -> withForeignPtr arg1 $ \argPtr1 ->gtk_window_move argPtr1 arg2 arg3)
{-# LINE 1587 "./Graphics/UI/Gtk/Windows/Window.chs" #-}
    (toWindow self)
    (fromIntegral x)
    (fromIntegral y)
windowParseGeometry :: (WindowClass self, GlibString string) => self
 -> string
 -> IO Bool
windowParseGeometry self geometry = liftM toBool $
  withUTFString geometry $ \geometryPtr ->
  (\(Window arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_window_parse_geometry argPtr1 arg2)
{-# LINE 1610 "./Graphics/UI/Gtk/Windows/Window.chs" #-}
     (toWindow self)
     geometryPtr
windowReshowWithInitialSize :: WindowClass self => self -> IO ()
windowReshowWithInitialSize self =
  (\(Window arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_window_reshow_with_initial_size argPtr1) (toWindow self)
windowResize :: WindowClass self => self
 -> Int 
 -> Int 
 -> IO ()
windowResize self width height =
  (\(Window arg1) arg2 arg3 -> withForeignPtr arg1 $ \argPtr1 ->gtk_window_resize argPtr1 arg2 arg3)
{-# LINE 1635 "./Graphics/UI/Gtk/Windows/Window.chs" #-}
    (toWindow self)
    (fromIntegral width)
    (fromIntegral height)
windowBeginResizeDrag :: WindowClass self => self
 -> WindowEdge 
 -> MouseButton 
 -> Int 
               
 -> Int 
               
 -> TimeStamp 
               
 -> IO ()
windowBeginResizeDrag self edge button rootX rootY timestamp =
  (\(Window arg1) arg2 arg3 arg4 arg5 arg6 -> withForeignPtr arg1 $ \argPtr1 ->gtk_window_begin_resize_drag argPtr1 arg2 arg3 arg4 arg5 arg6)
{-# LINE 1657 "./Graphics/UI/Gtk/Windows/Window.chs" #-}
    (toWindow self)
    ((fromIntegral . fromEnum) edge)
    ((fromIntegral . fromEnum) button)
    (fromIntegral rootX)
    (fromIntegral rootY)
    (fromIntegral timestamp)
windowBeginMoveDrag :: WindowClass self => self
 -> MouseButton 
 -> Int 
           
 -> Int 
           
 -> TimeStamp 
           
 -> IO ()
windowBeginMoveDrag self button rootX rootY timestamp =
  (\(Window arg1) arg2 arg3 arg4 arg5 -> withForeignPtr arg1 $ \argPtr1 ->gtk_window_begin_move_drag argPtr1 arg2 arg3 arg4 arg5)
{-# LINE 1681 "./Graphics/UI/Gtk/Windows/Window.chs" #-}
    (toWindow self)
    ((fromIntegral . fromEnum) button)
    (fromIntegral rootX)
    (fromIntegral rootY)
    (fromIntegral timestamp)
windowGetPosition :: WindowClass self => self
 -> IO (Int, Int) 
                  
windowGetPosition self =
  alloca $ \rootXPtr ->
  alloca $ \rootYPtr -> do
  (\(Window arg1) arg2 arg3 -> withForeignPtr arg1 $ \argPtr1 ->gtk_window_get_position argPtr1 arg2 arg3)
{-# LINE 1723 "./Graphics/UI/Gtk/Windows/Window.chs" #-}
    (toWindow self)
    rootXPtr
    rootYPtr
  rootX <- peek rootXPtr
  rootY <- peek rootYPtr
  return (fromIntegral rootX, fromIntegral rootY)
windowGetSize :: WindowClass self => self
 -> IO (Int, Int) 
windowGetSize self =
  alloca $ \widthPtr ->
  alloca $ \heightPtr -> do
  (\(Window arg1) arg2 arg3 -> withForeignPtr arg1 $ \argPtr1 ->gtk_window_get_size argPtr1 arg2 arg3)
{-# LINE 1774 "./Graphics/UI/Gtk/Windows/Window.chs" #-}
    (toWindow self)
    widthPtr
    heightPtr
  width <- peek widthPtr
  height <- peek heightPtr
  return (fromIntegral width, fromIntegral height)
windowSetTypeHint :: WindowClass self => self
 -> WindowTypeHint 
 -> IO ()
windowSetTypeHint self hint =
  (\(Window arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_window_set_type_hint argPtr1 arg2)
{-# LINE 1792 "./Graphics/UI/Gtk/Windows/Window.chs" #-}
    (toWindow self)
    ((fromIntegral . fromEnum) hint)
windowGetTypeHint :: WindowClass self => self
 -> IO WindowTypeHint 
windowGetTypeHint self =
  liftM (toEnum . fromIntegral) $
  (\(Window arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_window_get_type_hint argPtr1)
{-# LINE 1802 "./Graphics/UI/Gtk/Windows/Window.chs" #-}
    (toWindow self)
windowPresentWithTime :: WindowClass self => self
 -> TimeStamp 
              
              
 -> IO ()
windowPresentWithTime self timestamp =
  (\(Window arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_window_present_with_time argPtr1 arg2)
{-# LINE 1818 "./Graphics/UI/Gtk/Windows/Window.chs" #-}
    (toWindow self)
    (fromIntegral timestamp)
windowSetUrgencyHint :: WindowClass self => self
 -> Bool 
 -> IO ()
windowSetUrgencyHint self setting =
  (\(Window arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_window_set_urgency_hint argPtr1 arg2)
{-# LINE 1831 "./Graphics/UI/Gtk/Windows/Window.chs" #-}
    (toWindow self)
    (fromBool setting)
windowGetUrgencyHint :: WindowClass self => self
 -> IO Bool 
windowGetUrgencyHint self =
  liftM toBool $
  (\(Window arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_window_get_urgency_hint argPtr1)
{-# LINE 1843 "./Graphics/UI/Gtk/Windows/Window.chs" #-}
    (toWindow self)
windowSetGeometryHints :: (WindowClass self, WidgetClass widget) =>
    self 
 -> Maybe widget 
                     
                     
 -> Maybe (Int, Int) 
                     
 -> Maybe (Int, Int) 
                     
 -> Maybe (Int, Int) 
                     
                     
                     
                     
 -> Maybe (Int, Int) 
                     
 -> Maybe (Double, Double) 
                           
 -> IO ()
windowSetGeometryHints self geometryWidget
  minSize maxSize baseSize incSize aspect =
  allocaBytes 56 $ \geometryPtr -> do
  minSizeFlag <- case minSize of
    Nothing -> return 0
    Just (width, height) -> do
      (\ptr val -> do {pokeByteOff ptr 0 (val::CInt)}) geometryPtr (fromIntegral width)
      (\ptr val -> do {pokeByteOff ptr 4 (val::CInt)}) geometryPtr (fromIntegral height)
      return (fromEnum GdkHintMinSize)
  maxSizeFlag <- case maxSize of
    Nothing -> return 0
    Just (width, height) -> do
      (\ptr val -> do {pokeByteOff ptr 8 (val::CInt)}) geometryPtr (fromIntegral width)
      (\ptr val -> do {pokeByteOff ptr 12 (val::CInt)}) geometryPtr (fromIntegral height)
      return (fromEnum GdkHintMaxSize)
  baseSizeFlag <- case baseSize of
    Nothing -> return 0
    Just (width, height) -> do
      (\ptr val -> do {pokeByteOff ptr 16 (val::CInt)}) geometryPtr (fromIntegral width)
      (\ptr val -> do {pokeByteOff ptr 20 (val::CInt)}) geometryPtr (fromIntegral height)
      return (fromEnum GdkHintBaseSize)
  incSizeFlag <- case incSize of
    Nothing -> return 0
    Just (width, height) -> do
      (\ptr val -> do {pokeByteOff ptr 24 (val::CInt)}) geometryPtr (fromIntegral width)
      (\ptr val -> do {pokeByteOff ptr 28 (val::CInt)}) geometryPtr (fromIntegral height)
      return (fromEnum GdkHintResizeInc)
  aspectFlag <- case aspect of
    Nothing -> return 0
    Just (min, max) -> do
      (\ptr val -> do {pokeByteOff ptr 32 (val::CDouble)}) geometryPtr (realToFrac min)
      (\ptr val -> do {pokeByteOff ptr 40 (val::CDouble)}) geometryPtr (realToFrac max)
      return (fromEnum GdkHintAspect)
  (\(Window arg1) (Widget arg2) arg3 arg4 -> withForeignPtr arg1 $ \argPtr1 ->withForeignPtr arg2 $ \argPtr2 ->gtk_window_set_geometry_hints argPtr1 argPtr2 arg3 arg4)
{-# LINE 1934 "./Graphics/UI/Gtk/Windows/Window.chs" #-}
    (toWindow self)
    (maybe (Widget nullForeignPtr) toWidget geometryWidget)
    geometryPtr
    (fromIntegral $ minSizeFlag .|. maxSizeFlag .|. baseSizeFlag
                 .|. incSizeFlag .|. aspectFlag)
data GdkWindowHints = GdkHintPos
                    | GdkHintMinSize
                    | GdkHintMaxSize
                    | GdkHintBaseSize
                    | GdkHintAspect
                    | GdkHintResizeInc
                    | GdkHintWinGravity
                    | GdkHintUserPos
                    | GdkHintUserSize
instance Enum GdkWindowHints where
  fromEnum GdkHintPos = 1
  fromEnum GdkHintMinSize = 2
  fromEnum GdkHintMaxSize = 4
  fromEnum GdkHintBaseSize = 8
  fromEnum GdkHintAspect = 16
  fromEnum GdkHintResizeInc = 32
  fromEnum GdkHintWinGravity = 64
  fromEnum GdkHintUserPos = 128
  fromEnum GdkHintUserSize = 256
  toEnum 1 = GdkHintPos
  toEnum 2 = GdkHintMinSize
  toEnum 4 = GdkHintMaxSize
  toEnum 8 = GdkHintBaseSize
  toEnum 16 = GdkHintAspect
  toEnum 32 = GdkHintResizeInc
  toEnum 64 = GdkHintWinGravity
  toEnum 128 = GdkHintUserPos
  toEnum 256 = GdkHintUserSize
  toEnum unmatched = error ("GdkWindowHints.toEnum: Cannot match " ++ show unmatched)
  succ GdkHintPos = GdkHintMinSize
  succ GdkHintMinSize = GdkHintMaxSize
  succ GdkHintMaxSize = GdkHintBaseSize
  succ GdkHintBaseSize = GdkHintAspect
  succ GdkHintAspect = GdkHintResizeInc
  succ GdkHintResizeInc = GdkHintWinGravity
  succ GdkHintWinGravity = GdkHintUserPos
  succ GdkHintUserPos = GdkHintUserSize
  succ _ = undefined
  pred GdkHintMinSize = GdkHintPos
  pred GdkHintMaxSize = GdkHintMinSize
  pred GdkHintBaseSize = GdkHintMaxSize
  pred GdkHintAspect = GdkHintBaseSize
  pred GdkHintResizeInc = GdkHintAspect
  pred GdkHintWinGravity = GdkHintResizeInc
  pred GdkHintUserPos = GdkHintWinGravity
  pred GdkHintUserSize = GdkHintUserPos
  pred _ = undefined
  enumFromTo x y | fromEnum x == fromEnum y = [ y ]
                 | otherwise = x : enumFromTo (succ x) y
  enumFrom x = enumFromTo x GdkHintUserSize
  enumFromThen _ _ =     error "Enum GdkWindowHints: enumFromThen not implemented"
  enumFromThenTo _ _ _ =     error "Enum GdkWindowHints: enumFromThenTo not implemented"
{-# LINE 1972 "./Graphics/UI/Gtk/Windows/Window.chs" #-}
windowGetGroup :: WindowClass self => Maybe self
 -> IO WindowGroup 
windowGetGroup self =
  makeNewGObject mkWindowGroup $
  (\(Window arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_window_get_group argPtr1) (maybe (Window nullForeignPtr) toWindow self)
windowGetWindowType :: WindowClass self => self
                    -> IO WindowType 
windowGetWindowType self =
  liftM (toEnum . fromIntegral) $
  (\(Window arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_window_get_window_type argPtr1)
{-# LINE 1993 "./Graphics/UI/Gtk/Windows/Window.chs" #-}
    (toWindow self)
windowTitle :: (WindowClass self, GlibString string) => Attr self string
windowTitle = newAttr
  windowGetTitle
  windowSetTitle
windowType :: WindowClass self => ReadAttr self WindowType
windowType = readAttrFromEnumProperty "type"
  gtk_window_type_get_type
{-# LINE 2013 "./Graphics/UI/Gtk/Windows/Window.chs" #-}
windowAllowShrink :: WindowClass self => Attr self Bool
windowAllowShrink = newAttrFromBoolProperty "allow-shrink"
windowAllowGrow :: WindowClass self => Attr self Bool
windowAllowGrow = newAttrFromBoolProperty "allow-grow"
windowResizable :: WindowClass self => Attr self Bool
windowResizable = newAttr
  windowGetResizable
  windowSetResizable
windowHasResizeGrip :: WindowClass self => Attr self Bool
windowHasResizeGrip = newAttr
  windowGetHasResizeGrip
  windowSetHasResizeGrip
windowModal :: WindowClass self => Attr self Bool
windowModal = newAttr
  windowGetModal
  windowSetModal
windowOpacity :: WindowClass self => Attr self Double
windowOpacity = newAttrFromDoubleProperty "opacity"
windowFocus :: WindowClass self => Attr self (Maybe Widget)
windowFocus = newAttr
  windowGetFocus
  windowSetFocus
{-# LINE 2104 "./Graphics/UI/Gtk/Windows/Window.chs" #-}
windowIconList :: WindowClass self => Attr self [Pixbuf]
windowIconList = newAttr
  windowGetIconList
  windowSetIconList
windowMnemonicModifier :: WindowClass self => Attr self [Modifier]
windowMnemonicModifier = newAttr
  windowGetMnemonicModifier
  windowSetMnemonicModifier
windowMnemonicVisible :: WindowClass self => Attr self Bool
windowMnemonicVisible = newAttrFromBoolProperty "mnemonics-visible"
windowRole :: (WindowClass self, GlibString string) => Attr self string
windowRole = newAttrFromStringProperty "role"
windowStartupId :: (WindowClass self, GlibString string) => Attr self string
windowStartupId = newAttrFromStringProperty "startup-id"
windowWindowPosition :: WindowClass self => Attr self WindowPosition
windowWindowPosition = newAttrFromEnumProperty "window-position"
  gtk_window_position_get_type
{-# LINE 2165 "./Graphics/UI/Gtk/Windows/Window.chs" #-}
windowDefaultWidth :: WindowClass self => Attr self Int
windowDefaultWidth = newAttrFromIntProperty "default-width"
windowDefaultHeight :: WindowClass self => Attr self Int
windowDefaultHeight = newAttrFromIntProperty "default-height"
windowDeletable :: WindowClass self => Attr self Bool
windowDeletable = newAttrFromBoolProperty "deletable"
windowDestroyWithParent :: WindowClass self => Attr self Bool
windowDestroyWithParent = newAttr
  windowGetDestroyWithParent
  windowSetDestroyWithParent
windowIcon :: WindowClass self => Attr self (Maybe Pixbuf)
windowIcon = newAttr
  windowGetIcon
  windowSetIcon
windowIconName :: (WindowClass self, GlibString string) => Attr self string
windowIconName = newAttrFromStringProperty "icon-name"
windowScreen :: WindowClass self => Attr self Screen
windowScreen = newAttr
  windowGetScreen
  windowSetScreen
windowTypeHint :: WindowClass self => Attr self WindowTypeHint
windowTypeHint = newAttr
  windowGetTypeHint
  windowSetTypeHint
windowSkipTaskbarHint :: WindowClass self => Attr self Bool
windowSkipTaskbarHint = newAttr
  windowGetSkipTaskbarHint
  windowSetSkipTaskbarHint
windowSkipPagerHint :: WindowClass self => Attr self Bool
windowSkipPagerHint = newAttr
  windowGetSkipPagerHint
  windowSetSkipPagerHint
windowUrgencyHint :: WindowClass self => Attr self Bool
windowUrgencyHint = newAttr
  windowGetUrgencyHint
  windowSetUrgencyHint
windowAcceptFocus :: WindowClass self => Attr self Bool
windowAcceptFocus = newAttr
  windowGetAcceptFocus
  windowSetAcceptFocus
windowFocusOnMap :: WindowClass self => Attr self Bool
windowFocusOnMap = newAttr
  windowGetFocusOnMap
  windowSetFocusOnMap
windowDecorated :: WindowClass self => Attr self Bool
windowDecorated = newAttr
  windowGetDecorated
  windowSetDecorated
windowGravity :: WindowClass self => Attr self Gravity
windowGravity = newAttr
  windowGetGravity
  windowSetGravity
windowToplevelFocus :: WindowClass self => Attr self Bool
windowToplevelFocus = newAttrFromBoolProperty "has-toplevel-focus"
windowTransientFor :: (WindowClass self, WindowClass parent) => ReadWriteAttr self (Maybe Window) parent
windowTransientFor = newAttr
  windowGetTransientFor
  windowSetTransientFor
frameEvent :: WindowClass self => Signal self (EventM EAny Bool)
frameEvent = Signal (\after obj fun ->
                     connect_PTR__BOOL "frame-event" after obj (runReaderT fun))
keysChanged :: WindowClass self => Signal self (IO ())
keysChanged = Signal (connect_NONE__NONE "keys-changed")
setFocus :: WindowClass self => Signal self (Maybe Widget -> IO ())
setFocus = Signal (connect_MOBJECT__NONE "set-focus")
foreign import ccall safe "gtk_window_new"
  gtk_window_new :: (CInt -> (IO (Ptr Widget)))
foreign import ccall safe "gtk_window_set_title"
  gtk_window_set_title :: ((Ptr Window) -> ((Ptr CChar) -> (IO ())))
foreign import ccall safe "gtk_window_get_title"
  gtk_window_get_title :: ((Ptr Window) -> (IO (Ptr CChar)))
foreign import ccall safe "gtk_window_set_resizable"
  gtk_window_set_resizable :: ((Ptr Window) -> (CInt -> (IO ())))
foreign import ccall unsafe "gtk_window_get_resizable"
  gtk_window_get_resizable :: ((Ptr Window) -> (IO CInt))
foreign import ccall safe "gtk_window_set_has_resize_grip"
  gtk_window_set_has_resize_grip :: ((Ptr Window) -> (CInt -> (IO ())))
foreign import ccall unsafe "gtk_window_get_has_resize_grip"
  gtk_window_get_has_resize_grip :: ((Ptr Window) -> (IO CInt))
foreign import ccall safe "gtk_window_activate_focus"
  gtk_window_activate_focus :: ((Ptr Window) -> (IO CInt))
foreign import ccall safe "gtk_window_activate_default"
  gtk_window_activate_default :: ((Ptr Window) -> (IO CInt))
foreign import ccall safe "gtk_window_set_modal"
  gtk_window_set_modal :: ((Ptr Window) -> (CInt -> (IO ())))
foreign import ccall safe "gtk_window_get_modal"
  gtk_window_get_modal :: ((Ptr Window) -> (IO CInt))
foreign import ccall safe "gtk_window_set_default_size"
  gtk_window_set_default_size :: ((Ptr Window) -> (CInt -> (CInt -> (IO ()))))
foreign import ccall safe "gtk_window_add_mnemonic"
  gtk_window_add_mnemonic :: ((Ptr Window) -> (CUInt -> ((Ptr Widget) -> (IO ()))))
foreign import ccall safe "gtk_window_remove_mnemonic"
  gtk_window_remove_mnemonic :: ((Ptr Window) -> (CUInt -> ((Ptr Widget) -> (IO ()))))
foreign import ccall safe "gtk_window_mnemonic_activate"
  gtk_window_mnemonic_activate :: ((Ptr Window) -> (CUInt -> (CInt -> (IO CInt))))
foreign import ccall safe "gtk_window_set_mnemonic_modifier"
  gtk_window_set_mnemonic_modifier :: ((Ptr Window) -> (CInt -> (IO ())))
foreign import ccall safe "gtk_window_get_mnemonic_modifier"
  gtk_window_get_mnemonic_modifier :: ((Ptr Window) -> (IO CInt))
foreign import ccall safe "gtk_window_activate_key"
  gtk_window_activate_key :: ((Ptr Window) -> ((Ptr ()) -> (IO CInt)))
foreign import ccall safe "gtk_window_propagate_key_event"
  gtk_window_propagate_key_event :: ((Ptr Window) -> ((Ptr ()) -> (IO CInt)))
foreign import ccall safe "gtk_window_get_default_size"
  gtk_window_get_default_size :: ((Ptr Window) -> ((Ptr CInt) -> ((Ptr CInt) -> (IO ()))))
foreign import ccall safe "gtk_window_set_position"
  gtk_window_set_position :: ((Ptr Window) -> (CInt -> (IO ())))
foreign import ccall safe "gtk_window_set_transient_for"
  gtk_window_set_transient_for :: ((Ptr Window) -> ((Ptr Window) -> (IO ())))
foreign import ccall safe "gtk_window_get_transient_for"
  gtk_window_get_transient_for :: ((Ptr Window) -> (IO (Ptr Window)))
foreign import ccall safe "gtk_window_set_destroy_with_parent"
  gtk_window_set_destroy_with_parent :: ((Ptr Window) -> (CInt -> (IO ())))
foreign import ccall safe "gtk_window_get_destroy_with_parent"
  gtk_window_get_destroy_with_parent :: ((Ptr Window) -> (IO CInt))
foreign import ccall safe "gtk_window_is_active"
  gtk_window_is_active :: ((Ptr Window) -> (IO CInt))
foreign import ccall safe "gtk_window_has_toplevel_focus"
  gtk_window_has_toplevel_focus :: ((Ptr Window) -> (IO CInt))
foreign import ccall unsafe "gtk_window_list_toplevels"
  gtk_window_list_toplevels :: (IO (Ptr ()))
foreign import ccall unsafe "gtk_window_get_focus"
  gtk_window_get_focus :: ((Ptr Window) -> (IO (Ptr Widget)))
foreign import ccall unsafe "gtk_window_set_focus"
  gtk_window_set_focus :: ((Ptr Window) -> ((Ptr Widget) -> (IO ())))
foreign import ccall safe "gtk_window_get_default_widget"
  gtk_window_get_default_widget :: ((Ptr Window) -> (IO (Ptr Widget)))
foreign import ccall safe "gtk_window_present"
  gtk_window_present :: ((Ptr Window) -> (IO ()))
foreign import ccall safe "gtk_window_deiconify"
  gtk_window_deiconify :: ((Ptr Window) -> (IO ()))
foreign import ccall safe "gtk_window_iconify"
  gtk_window_iconify :: ((Ptr Window) -> (IO ()))
foreign import ccall safe "gtk_window_maximize"
  gtk_window_maximize :: ((Ptr Window) -> (IO ()))
foreign import ccall safe "gtk_window_unmaximize"
  gtk_window_unmaximize :: ((Ptr Window) -> (IO ()))
foreign import ccall safe "gtk_window_fullscreen"
  gtk_window_fullscreen :: ((Ptr Window) -> (IO ()))
foreign import ccall safe "gtk_window_unfullscreen"
  gtk_window_unfullscreen :: ((Ptr Window) -> (IO ()))
foreign import ccall safe "gtk_window_set_keep_above"
  gtk_window_set_keep_above :: ((Ptr Window) -> (CInt -> (IO ())))
foreign import ccall safe "gtk_window_set_keep_below"
  gtk_window_set_keep_below :: ((Ptr Window) -> (CInt -> (IO ())))
foreign import ccall safe "gtk_window_set_skip_taskbar_hint"
  gtk_window_set_skip_taskbar_hint :: ((Ptr Window) -> (CInt -> (IO ())))
foreign import ccall safe "gtk_window_get_skip_taskbar_hint"
  gtk_window_get_skip_taskbar_hint :: ((Ptr Window) -> (IO CInt))
foreign import ccall safe "gtk_window_set_skip_pager_hint"
  gtk_window_set_skip_pager_hint :: ((Ptr Window) -> (CInt -> (IO ())))
foreign import ccall safe "gtk_window_get_skip_pager_hint"
  gtk_window_get_skip_pager_hint :: ((Ptr Window) -> (IO CInt))
foreign import ccall safe "gtk_window_set_accept_focus"
  gtk_window_set_accept_focus :: ((Ptr Window) -> (CInt -> (IO ())))
foreign import ccall safe "gtk_window_get_accept_focus"
  gtk_window_get_accept_focus :: ((Ptr Window) -> (IO CInt))
foreign import ccall safe "gtk_window_set_focus_on_map"
  gtk_window_set_focus_on_map :: ((Ptr Window) -> (CInt -> (IO ())))
foreign import ccall safe "gtk_window_get_focus_on_map"
  gtk_window_get_focus_on_map :: ((Ptr Window) -> (IO CInt))
foreign import ccall safe "gtk_window_set_startup_id"
  gtk_window_set_startup_id :: ((Ptr Window) -> ((Ptr CChar) -> (IO ())))
foreign import ccall safe "gtk_window_set_decorated"
  gtk_window_set_decorated :: ((Ptr Window) -> (CInt -> (IO ())))
foreign import ccall safe "gtk_window_get_decorated"
  gtk_window_get_decorated :: ((Ptr Window) -> (IO CInt))
foreign import ccall safe "gtk_window_stick"
  gtk_window_stick :: ((Ptr Window) -> (IO ()))
foreign import ccall safe "gtk_window_unstick"
  gtk_window_unstick :: ((Ptr Window) -> (IO ()))
foreign import ccall safe "gtk_window_add_accel_group"
  gtk_window_add_accel_group :: ((Ptr Window) -> ((Ptr AccelGroup) -> (IO ())))
foreign import ccall safe "gtk_window_remove_accel_group"
  gtk_window_remove_accel_group :: ((Ptr Window) -> ((Ptr AccelGroup) -> (IO ())))
foreign import ccall safe "gtk_window_set_icon"
  gtk_window_set_icon :: ((Ptr Window) -> ((Ptr Pixbuf) -> (IO ())))
foreign import ccall safe "gtk_window_get_icon"
  gtk_window_get_icon :: ((Ptr Window) -> (IO (Ptr Pixbuf)))
foreign import ccall safe "gtk_window_set_icon_list"
  gtk_window_set_icon_list :: ((Ptr Window) -> ((Ptr ()) -> (IO ())))
foreign import ccall safe "gtk_window_get_icon_list"
  gtk_window_get_icon_list :: ((Ptr Window) -> (IO (Ptr ())))
foreign import ccall safe "gtk_window_set_default_icon_list"
  gtk_window_set_default_icon_list :: ((Ptr ()) -> (IO ()))
foreign import ccall safe "gtk_window_get_default_icon_list"
  gtk_window_get_default_icon_list :: (IO (Ptr ()))
foreign import ccall safe "gtk_window_set_default_icon_name"
  gtk_window_set_default_icon_name :: ((Ptr CChar) -> (IO ()))
foreign import ccall safe "gtk_window_set_default_icon"
  gtk_window_set_default_icon :: ((Ptr Pixbuf) -> (IO ()))
foreign import ccall safe "gtk_window_set_default_icon_from_file"
  gtk_window_set_default_icon_from_file :: ((Ptr CChar) -> ((Ptr (Ptr ())) -> (IO CInt)))
foreign import ccall safe "gtk_window_get_default_icon_name"
  gtk_window_get_default_icon_name :: (IO (Ptr CChar))
foreign import ccall safe "gtk_window_set_screen"
  gtk_window_set_screen :: ((Ptr Window) -> ((Ptr Screen) -> (IO ())))
foreign import ccall safe "gtk_window_get_screen"
  gtk_window_get_screen :: ((Ptr Window) -> (IO (Ptr Screen)))
foreign import ccall safe "gtk_window_set_icon_from_file"
  gtk_window_set_icon_from_file :: ((Ptr Window) -> ((Ptr CChar) -> ((Ptr (Ptr ())) -> (IO CInt))))
foreign import ccall safe "gtk_window_set_auto_startup_notification"
  gtk_window_set_auto_startup_notification :: (CInt -> (IO ()))
foreign import ccall safe "gtk_window_set_gravity"
  gtk_window_set_gravity :: ((Ptr Window) -> (CInt -> (IO ())))
foreign import ccall safe "gtk_window_get_gravity"
  gtk_window_get_gravity :: ((Ptr Window) -> (IO CInt))
foreign import ccall safe "gtk_window_move"
  gtk_window_move :: ((Ptr Window) -> (CInt -> (CInt -> (IO ()))))
foreign import ccall safe "gtk_window_parse_geometry"
  gtk_window_parse_geometry :: ((Ptr Window) -> ((Ptr CChar) -> (IO CInt)))
foreign import ccall safe "gtk_window_reshow_with_initial_size"
  gtk_window_reshow_with_initial_size :: ((Ptr Window) -> (IO ()))
foreign import ccall safe "gtk_window_resize"
  gtk_window_resize :: ((Ptr Window) -> (CInt -> (CInt -> (IO ()))))
foreign import ccall safe "gtk_window_begin_resize_drag"
  gtk_window_begin_resize_drag :: ((Ptr Window) -> (CInt -> (CInt -> (CInt -> (CInt -> (CUInt -> (IO ())))))))
foreign import ccall safe "gtk_window_begin_move_drag"
  gtk_window_begin_move_drag :: ((Ptr Window) -> (CInt -> (CInt -> (CInt -> (CUInt -> (IO ()))))))
foreign import ccall safe "gtk_window_get_position"
  gtk_window_get_position :: ((Ptr Window) -> ((Ptr CInt) -> ((Ptr CInt) -> (IO ()))))
foreign import ccall safe "gtk_window_get_size"
  gtk_window_get_size :: ((Ptr Window) -> ((Ptr CInt) -> ((Ptr CInt) -> (IO ()))))
foreign import ccall safe "gtk_window_set_type_hint"
  gtk_window_set_type_hint :: ((Ptr Window) -> (CInt -> (IO ())))
foreign import ccall safe "gtk_window_get_type_hint"
  gtk_window_get_type_hint :: ((Ptr Window) -> (IO CInt))
foreign import ccall safe "gtk_window_present_with_time"
  gtk_window_present_with_time :: ((Ptr Window) -> (CUInt -> (IO ())))
foreign import ccall safe "gtk_window_set_urgency_hint"
  gtk_window_set_urgency_hint :: ((Ptr Window) -> (CInt -> (IO ())))
foreign import ccall safe "gtk_window_get_urgency_hint"
  gtk_window_get_urgency_hint :: ((Ptr Window) -> (IO CInt))
foreign import ccall safe "gtk_window_set_geometry_hints"
  gtk_window_set_geometry_hints :: ((Ptr Window) -> ((Ptr Widget) -> ((Ptr ()) -> (CInt -> (IO ())))))
foreign import ccall safe "gtk_window_get_group"
  gtk_window_get_group :: ((Ptr Window) -> (IO (Ptr WindowGroup)))
foreign import ccall safe "gtk_window_get_window_type"
  gtk_window_get_window_type :: ((Ptr Window) -> (IO CInt))
foreign import ccall unsafe "gtk_window_type_get_type"
  gtk_window_type_get_type :: CULong
foreign import ccall unsafe "gtk_window_position_get_type"
  gtk_window_position_get_type :: CULong