module Graphics.UI.Gtk.WebKit.DOM.Window(
getSelection,
blur,
print,
stop,
alert,
confirm,
prompt,
find,
scrollBy,
scrollTo,
scroll,
moveBy,
moveTo,
resizeBy,
resizeTo,
matchMedia,
getComputedStyle,
webkitConvertPointFromPageToNode,
webkitConvertPointFromNodeToPage,
captureEvents,
releaseEvents,
getWebkitStorageInfo,
getScreen,
getHistory,
getLocationbar,
getMenubar,
getPersonalbar,
getScrollbars,
getStatusbar,
getToolbar,
getNavigator,
getClientInformation,
getFrameElement,
getOffscreenBuffering,
getOuterHeight,
getOuterWidth,
getInnerHeight,
getInnerWidth,
getScreenX,
getScreenY,
getScreenLeft,
getScreenTop,
getScrollX,
getScrollY,
getPageXOffset,
getPageYOffset,
getClosed,
getLength,
setName,
getName,
setStatus,
getStatus,
setDefaultStatus,
getDefaultStatus,
getSelf,
getWindow,
getFrames,
getOpener,
getParent,
getTop,
getDocument,
getStyleMedia,
getDevicePixelRatio,
getApplicationCache,
getSessionStorage,
getLocalStorage,
getPerformance,
getCSS,
abort,
beforeUnload,
blurEvent,
canPlay,
canPlayThrough,
change,
click,
contextMenu,
dblClick,
drag,
dragEnd,
dragEnter,
dragLeave,
dragOver,
dragStart,
drop,
durationChange,
emptied,
ended,
error,
focusEvent,
hashChange,
input,
invalid,
keyDown,
keyPress,
keyUp,
load,
loadedData,
loadedMetadata,
loadStart,
message,
mouseDown,
mouseEnter,
mouseLeave,
mouseMove,
mouseOut,
mouseOver,
mouseUp,
mouseWheel,
offline,
online,
pageHide,
pageShow,
pause,
play,
playing,
popState,
progress,
rateChange,
resize,
scrollEvent,
seeked,
seeking,
select,
stalled,
storage,
submit,
suspend,
timeUpdate,
unload,
volumeChange,
waiting,
wheel,
reset,
search,
webKitAnimationEnd,
webKitAnimationIteration,
webKitAnimationStart,
animationEnd,
animationIteration,
animationStart,
webKitTransitionEnd,
transitionEnd,
touchStart,
touchMove,
touchEnd,
touchCancel,
gestureStart,
gestureChange,
gestureEnd,
deviceMotion,
deviceOrientation,
webKitDeviceProximity,
webKitWillRevealBottom,
webKitWillRevealLeft,
webKitWillRevealRight,
webKitWillRevealTop,
Window,
castToWindow,
gTypeWindow,
WindowClass,
toWindow,
) where
import Prelude hiding (drop, error, print)
import Data.Typeable (Typeable)
import Foreign.Marshal (maybePeek, maybeWith)
import System.Glib.FFI (maybeNull, withForeignPtr, nullForeignPtr, Ptr, nullPtr, castPtr, Word, Int64, Word64, CChar(..), CInt(..), CUInt(..), CLong(..), CULong(..), CLLong(..), CULLong(..), CShort(..), CUShort(..), CFloat(..), CDouble(..), toBool, fromBool)
import System.Glib.UTFString (GlibString(..), readUTFString)
import Control.Applicative ((<$>))
import Control.Monad (void)
import Control.Monad.IO.Class (MonadIO(..))
import System.Glib.GError
import Graphics.UI.Gtk.WebKit.DOM.EventTargetClosures
import Graphics.UI.Gtk.WebKit.DOM.EventM
import Graphics.UI.Gtk.WebKit.Types
import Graphics.UI.Gtk.WebKit.DOM.Enums
 
getSelection ::
             (MonadIO m, WindowClass self) => self -> m (Maybe Selection)
getSelection self
  = liftIO
      (maybeNull (makeNewGObject mkSelection)
         ((\(Window arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_dom_window_get_selection argPtr1) (toWindow self)))
 
blur :: (MonadIO m, WindowClass self) => self -> m ()
blur self
  = liftIO ((\(Window arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_dom_window_blur argPtr1) (toWindow self))
 
print :: (MonadIO m, WindowClass self) => self -> m ()
print self
  = liftIO ((\(Window arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_dom_window_print argPtr1) (toWindow self))
 
stop :: (MonadIO m, WindowClass self) => self -> m ()
stop self
  = liftIO ((\(Window arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_dom_window_stop argPtr1) (toWindow self))
 
alert ::
      (MonadIO m, WindowClass self, GlibString string) =>
        self -> string -> m ()
alert self message
  = liftIO
      (withUTFString message $
         \ messagePtr ->
           (\(Window arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_dom_window_alert argPtr1 arg2) (toWindow self) messagePtr)
 
confirm ::
        (MonadIO m, WindowClass self, GlibString string) =>
          self -> string -> m Bool
confirm self message
  = liftIO
      (toBool <$>
         (withUTFString message $
            \ messagePtr ->
              (\(Window arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_dom_window_confirm argPtr1 arg2) (toWindow self)
                messagePtr))
 
prompt ::
       (MonadIO m, WindowClass self, GlibString string) =>
         self -> string -> (Maybe string) -> m (Maybe string)
prompt self message defaultValue
  = liftIO
      ((maybeWith withUTFString defaultValue $
          \ defaultValuePtr ->
            withUTFString message $
              \ messagePtr ->
                (\(Window arg1) arg2 arg3 -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_dom_window_prompt argPtr1 arg2 arg3) (toWindow self) messagePtr
              defaultValuePtr)
         >>=
         maybePeek readUTFString)
 
find ::
     (MonadIO m, WindowClass self, GlibString string) =>
       self ->
         string -> Bool -> Bool -> Bool -> Bool -> Bool -> Bool -> m Bool
find self string caseSensitive backwards wrap wholeWord
  searchInFrames showDialog
  = liftIO
      (toBool <$>
         (withUTFString string $
            \ stringPtr ->
              (\(Window arg1) arg2 arg3 arg4 arg5 arg6 arg7 arg8 -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_dom_window_find argPtr1 arg2 arg3 arg4 arg5 arg6 arg7 arg8) (toWindow self) stringPtr
            (fromBool caseSensitive)
            (fromBool backwards)
            (fromBool wrap)
            (fromBool wholeWord)
            (fromBool searchInFrames)
            (fromBool showDialog)))
 
scrollBy ::
         (MonadIO m, WindowClass self) => self -> Int -> Int -> m ()
scrollBy self x y
  = liftIO
      ((\(Window arg1) arg2 arg3 -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_dom_window_scroll_by argPtr1 arg2 arg3) (toWindow self)
         (fromIntegral x)
         (fromIntegral y))
 
scrollTo ::
         (MonadIO m, WindowClass self) => self -> Int -> Int -> m ()
scrollTo self x y
  = liftIO
      ((\(Window arg1) arg2 arg3 -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_dom_window_scroll_to argPtr1 arg2 arg3) (toWindow self)
         (fromIntegral x)
         (fromIntegral y))
 
scroll ::
       (MonadIO m, WindowClass self) => self -> Int -> Int -> m ()
scroll self x y
  = liftIO
      ((\(Window arg1) arg2 arg3 -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_dom_window_scroll argPtr1 arg2 arg3) (toWindow self)
         (fromIntegral x)
         (fromIntegral y))
 
moveBy ::
       (MonadIO m, WindowClass self) => self -> Float -> Float -> m ()
moveBy self x y
  = liftIO
      ((\(Window arg1) arg2 arg3 -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_dom_window_move_by argPtr1 arg2 arg3) (toWindow self)
         (realToFrac x)
         (realToFrac y))
 
moveTo ::
       (MonadIO m, WindowClass self) => self -> Float -> Float -> m ()
moveTo self x y
  = liftIO
      ((\(Window arg1) arg2 arg3 -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_dom_window_move_to argPtr1 arg2 arg3) (toWindow self)
         (realToFrac x)
         (realToFrac y))
 
resizeBy ::
         (MonadIO m, WindowClass self) => self -> Float -> Float -> m ()
resizeBy self x y
  = liftIO
      ((\(Window arg1) arg2 arg3 -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_dom_window_resize_by argPtr1 arg2 arg3) (toWindow self)
         (realToFrac x)
         (realToFrac y))
 
resizeTo ::
         (MonadIO m, WindowClass self) => self -> Float -> Float -> m ()
resizeTo self width height
  = liftIO
      ((\(Window arg1) arg2 arg3 -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_dom_window_resize_to argPtr1 arg2 arg3) (toWindow self)
         (realToFrac width)
         (realToFrac height))
 
matchMedia ::
           (MonadIO m, WindowClass self, GlibString string) =>
             self -> string -> m (Maybe MediaQueryList)
matchMedia self query
  = liftIO
      (maybeNull (makeNewGObject mkMediaQueryList)
         (withUTFString query $
            \ queryPtr ->
              (\(Window arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_dom_window_match_media argPtr1 arg2) (toWindow self)
                queryPtr))
 
getComputedStyle ::
                 (MonadIO m, WindowClass self, ElementClass element,
                  GlibString string) =>
                   self ->
                     Maybe element -> (Maybe string) -> m (Maybe CSSStyleDeclaration)
getComputedStyle self element pseudoElement
  = liftIO
      (maybeNull (makeNewGObject mkCSSStyleDeclaration)
         (maybeWith withUTFString pseudoElement $
            \ pseudoElementPtr ->
              (\(Window arg1) (Element arg2) arg3 -> withForeignPtr arg1 $ \argPtr1 ->withForeignPtr arg2 $ \argPtr2 ->webkit_dom_dom_window_get_computed_style argPtr1 argPtr2 arg3) (toWindow self)
                (maybe (Element nullForeignPtr) toElement element)
                pseudoElementPtr))
 
webkitConvertPointFromPageToNode ::
                                 (MonadIO m, WindowClass self, NodeClass node,
                                  WebKitPointClass p) =>
                                   self -> Maybe node -> Maybe p -> m (Maybe WebKitPoint)
webkitConvertPointFromPageToNode self node p
  = liftIO
      (maybeNull (makeNewGObject mkWebKitPoint)
         ((\(Window arg1) (Node arg2) (WebKitPoint arg3) -> withForeignPtr arg1 $ \argPtr1 ->withForeignPtr arg2 $ \argPtr2 ->withForeignPtr arg3 $ \argPtr3 ->webkit_dom_dom_window_webkit_convert_point_from_page_to_node argPtr1 argPtr2 argPtr3)
            (toWindow self)
            (maybe (Node nullForeignPtr) toNode node)
            (maybe (WebKitPoint nullForeignPtr) toWebKitPoint p)))
 
webkitConvertPointFromNodeToPage ::
                                 (MonadIO m, WindowClass self, NodeClass node,
                                  WebKitPointClass p) =>
                                   self -> Maybe node -> Maybe p -> m (Maybe WebKitPoint)
webkitConvertPointFromNodeToPage self node p
  = liftIO
      (maybeNull (makeNewGObject mkWebKitPoint)
         ((\(Window arg1) (Node arg2) (WebKitPoint arg3) -> withForeignPtr arg1 $ \argPtr1 ->withForeignPtr arg2 $ \argPtr2 ->withForeignPtr arg3 $ \argPtr3 ->webkit_dom_dom_window_webkit_convert_point_from_node_to_page argPtr1 argPtr2 argPtr3)
            (toWindow self)
            (maybe (Node nullForeignPtr) toNode node)
            (maybe (WebKitPoint nullForeignPtr) toWebKitPoint p)))
 
captureEvents :: (MonadIO m, WindowClass self) => self -> m ()
captureEvents self
  = liftIO
      ((\(Window arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_dom_window_capture_events argPtr1) (toWindow self))
 
releaseEvents :: (MonadIO m, WindowClass self) => self -> m ()
releaseEvents self
  = liftIO
      ((\(Window arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_dom_window_release_events argPtr1) (toWindow self))
getWebkitStorageInfo ::
                     (MonadIO m, WindowClass self) => self -> m (Maybe StorageInfo)
getWebkitStorageInfo self
  = liftIO
      (maybeNull (makeNewGObject mkStorageInfo)
         ((\(Window arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_dom_window_get_webkit_storage_info argPtr1)
            (toWindow self)))
 
getScreen ::
          (MonadIO m, WindowClass self) => self -> m (Maybe Screen)
getScreen self
  = liftIO
      (maybeNull (makeNewGObject mkScreen)
         ((\(Window arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_dom_window_get_screen argPtr1) (toWindow self)))
 
getHistory ::
           (MonadIO m, WindowClass self) => self -> m (Maybe History)
getHistory self
  = liftIO
      (maybeNull (makeNewGObject mkHistory)
         ((\(Window arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_dom_window_get_history argPtr1) (toWindow self)))
getLocationbar ::
               (MonadIO m, WindowClass self) => self -> m (Maybe BarProp)
getLocationbar self
  = liftIO
      (maybeNull (makeNewGObject mkBarProp)
         ((\(Window arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_dom_window_get_locationbar argPtr1) (toWindow self)))
 
getMenubar ::
           (MonadIO m, WindowClass self) => self -> m (Maybe BarProp)
getMenubar self
  = liftIO
      (maybeNull (makeNewGObject mkBarProp)
         ((\(Window arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_dom_window_get_menubar argPtr1) (toWindow self)))
 
getPersonalbar ::
               (MonadIO m, WindowClass self) => self -> m (Maybe BarProp)
getPersonalbar self
  = liftIO
      (maybeNull (makeNewGObject mkBarProp)
         ((\(Window arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_dom_window_get_personalbar argPtr1) (toWindow self)))
 
getScrollbars ::
              (MonadIO m, WindowClass self) => self -> m (Maybe BarProp)
getScrollbars self
  = liftIO
      (maybeNull (makeNewGObject mkBarProp)
         ((\(Window arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_dom_window_get_scrollbars argPtr1) (toWindow self)))
 
getStatusbar ::
             (MonadIO m, WindowClass self) => self -> m (Maybe BarProp)
getStatusbar self
  = liftIO
      (maybeNull (makeNewGObject mkBarProp)
         ((\(Window arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_dom_window_get_statusbar argPtr1) (toWindow self)))
 
getToolbar ::
           (MonadIO m, WindowClass self) => self -> m (Maybe BarProp)
getToolbar self
  = liftIO
      (maybeNull (makeNewGObject mkBarProp)
         ((\(Window arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_dom_window_get_toolbar argPtr1) (toWindow self)))
 
getNavigator ::
             (MonadIO m, WindowClass self) => self -> m (Maybe Navigator)
getNavigator self
  = liftIO
      (maybeNull (makeNewGObject mkNavigator)
         ((\(Window arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_dom_window_get_navigator argPtr1) (toWindow self)))
 
getClientInformation ::
                     (MonadIO m, WindowClass self) => self -> m (Maybe Navigator)
getClientInformation self
  = liftIO
      (maybeNull (makeNewGObject mkNavigator)
         ((\(Window arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_dom_window_get_client_information argPtr1)
            (toWindow self)))
 
getFrameElement ::
                (MonadIO m, WindowClass self) => self -> m (Maybe Element)
getFrameElement self
  = liftIO
      (maybeNull (makeNewGObject mkElement)
         ((\(Window arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_dom_window_get_frame_element argPtr1)
            (toWindow self)))
 
getOffscreenBuffering ::
                      (MonadIO m, WindowClass self) => self -> m Bool
getOffscreenBuffering self
  = liftIO
      (toBool <$>
         ((\(Window arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_dom_window_get_offscreen_buffering argPtr1)
            (toWindow self)))
 
getOuterHeight :: (MonadIO m, WindowClass self) => self -> m Int
getOuterHeight self
  = liftIO
      (fromIntegral <$>
         ((\(Window arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_dom_window_get_outer_height argPtr1)
            (toWindow self)))
 
getOuterWidth :: (MonadIO m, WindowClass self) => self -> m Int
getOuterWidth self
  = liftIO
      (fromIntegral <$>
         ((\(Window arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_dom_window_get_outer_width argPtr1) (toWindow self)))
 
getInnerHeight :: (MonadIO m, WindowClass self) => self -> m Int
getInnerHeight self
  = liftIO
      (fromIntegral <$>
         ((\(Window arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_dom_window_get_inner_height argPtr1)
            (toWindow self)))
 
getInnerWidth :: (MonadIO m, WindowClass self) => self -> m Int
getInnerWidth self
  = liftIO
      (fromIntegral <$>
         ((\(Window arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_dom_window_get_inner_width argPtr1) (toWindow self)))
 
getScreenX :: (MonadIO m, WindowClass self) => self -> m Int
getScreenX self
  = liftIO
      (fromIntegral <$>
         ((\(Window arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_dom_window_get_screen_x argPtr1) (toWindow self)))
 
getScreenY :: (MonadIO m, WindowClass self) => self -> m Int
getScreenY self
  = liftIO
      (fromIntegral <$>
         ((\(Window arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_dom_window_get_screen_y argPtr1) (toWindow self)))
 
getScreenLeft :: (MonadIO m, WindowClass self) => self -> m Int
getScreenLeft self
  = liftIO
      (fromIntegral <$>
         ((\(Window arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_dom_window_get_screen_left argPtr1) (toWindow self)))
 
getScreenTop :: (MonadIO m, WindowClass self) => self -> m Int
getScreenTop self
  = liftIO
      (fromIntegral <$>
         ((\(Window arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_dom_window_get_screen_top argPtr1) (toWindow self)))
 
getScrollX :: (MonadIO m, WindowClass self) => self -> m Int
getScrollX self
  = liftIO
      (fromIntegral <$>
         ((\(Window arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_dom_window_get_scroll_x argPtr1) (toWindow self)))
 
getScrollY :: (MonadIO m, WindowClass self) => self -> m Int
getScrollY self
  = liftIO
      (fromIntegral <$>
         ((\(Window arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_dom_window_get_scroll_y argPtr1) (toWindow self)))
 
getPageXOffset :: (MonadIO m, WindowClass self) => self -> m Int
getPageXOffset self
  = liftIO
      (fromIntegral <$>
         ((\(Window arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_dom_window_get_page_x_offset argPtr1)
            (toWindow self)))
 
getPageYOffset :: (MonadIO m, WindowClass self) => self -> m Int
getPageYOffset self
  = liftIO
      (fromIntegral <$>
         ((\(Window arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_dom_window_get_page_y_offset argPtr1)
            (toWindow self)))
 
getClosed :: (MonadIO m, WindowClass self) => self -> m Bool
getClosed self
  = liftIO
      (toBool <$>
         ((\(Window arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_dom_window_get_closed argPtr1) (toWindow self)))
 
getLength :: (MonadIO m, WindowClass self) => self -> m Word
getLength self
  = liftIO
      (fromIntegral <$>
         ((\(Window arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_dom_window_get_length argPtr1) (toWindow self)))
 
setName ::
        (MonadIO m, WindowClass self, GlibString string) =>
          self -> string -> m ()
setName self val
  = liftIO
      (withUTFString val $
         \ valPtr ->
           (\(Window arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_dom_window_set_name argPtr1 arg2) (toWindow self) valPtr)
 
getName ::
        (MonadIO m, WindowClass self, GlibString string) =>
          self -> m string
getName self
  = liftIO
      (((\(Window arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_dom_window_get_name argPtr1) (toWindow self)) >>=
         readUTFString)
 
setStatus ::
          (MonadIO m, WindowClass self, GlibString string) =>
            self -> string -> m ()
setStatus self val
  = liftIO
      (withUTFString val $
         \ valPtr ->
           (\(Window arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_dom_window_set_status argPtr1 arg2) (toWindow self) valPtr)
 
getStatus ::
          (MonadIO m, WindowClass self, GlibString string) =>
            self -> m string
getStatus self
  = liftIO
      (((\(Window arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_dom_window_get_status argPtr1) (toWindow self)) >>=
         readUTFString)
 
setDefaultStatus ::
                 (MonadIO m, WindowClass self, GlibString string) =>
                   self -> string -> m ()
setDefaultStatus self val
  = liftIO
      (withUTFString val $
         \ valPtr ->
           (\(Window arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_dom_window_set_default_status argPtr1 arg2) (toWindow self)
             valPtr)
 
getDefaultStatus ::
                 (MonadIO m, WindowClass self, GlibString string) =>
                   self -> m string
getDefaultStatus self
  = liftIO
      (((\(Window arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_dom_window_get_default_status argPtr1)
          (toWindow self))
         >>=
         readUTFString)
 
getSelf ::
        (MonadIO m, WindowClass self) => self -> m (Maybe Window)
getSelf self
  = liftIO
      (maybeNull (makeNewGObject mkWindow)
         ((\(Window arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_dom_window_get_self argPtr1) (toWindow self)))
 
getWindow ::
          (MonadIO m, WindowClass self) => self -> m (Maybe Window)
getWindow self
  = liftIO
      (maybeNull (makeNewGObject mkWindow)
         ((\(Window arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_dom_window_get_window argPtr1) (toWindow self)))
 
getFrames ::
          (MonadIO m, WindowClass self) => self -> m (Maybe Window)
getFrames self
  = liftIO
      (maybeNull (makeNewGObject mkWindow)
         ((\(Window arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_dom_window_get_frames argPtr1) (toWindow self)))
 
getOpener ::
          (MonadIO m, WindowClass self) => self -> m (Maybe Window)
getOpener self
  = liftIO
      (maybeNull (makeNewGObject mkWindow)
         ((\(Window arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_dom_window_get_opener argPtr1) (toWindow self)))
 
getParent ::
          (MonadIO m, WindowClass self) => self -> m (Maybe Window)
getParent self
  = liftIO
      (maybeNull (makeNewGObject mkWindow)
         ((\(Window arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_dom_window_get_parent argPtr1) (toWindow self)))
 
getTop :: (MonadIO m, WindowClass self) => self -> m (Maybe Window)
getTop self
  = liftIO
      (maybeNull (makeNewGObject mkWindow)
         ((\(Window arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_dom_window_get_top argPtr1) (toWindow self)))
 
getDocument ::
            (MonadIO m, WindowClass self) => self -> m (Maybe Document)
getDocument self
  = liftIO
      (maybeNull (makeNewGObject mkDocument)
         ((\(Window arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_dom_window_get_document argPtr1) (toWindow self)))
 
getStyleMedia ::
              (MonadIO m, WindowClass self) => self -> m (Maybe StyleMedia)
getStyleMedia self
  = liftIO
      (maybeNull (makeNewGObject mkStyleMedia)
         ((\(Window arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_dom_window_get_style_media argPtr1) (toWindow self)))
 
getDevicePixelRatio ::
                    (MonadIO m, WindowClass self) => self -> m Double
getDevicePixelRatio self
  = liftIO
      (realToFrac <$>
         ((\(Window arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_dom_window_get_device_pixel_ratio argPtr1)
            (toWindow self)))
 
getApplicationCache ::
                    (MonadIO m, WindowClass self) => self -> m (Maybe ApplicationCache)
getApplicationCache self
  = liftIO
      (maybeNull (makeNewGObject mkApplicationCache)
         ((\(Window arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_dom_window_get_application_cache argPtr1)
            (toWindow self)))
 
getSessionStorage ::
                  (MonadIO m, WindowClass self) => self -> m (Maybe Storage)
getSessionStorage self
  = liftIO
      (maybeNull (makeNewGObject mkStorage)
         (propagateGError $
            \ errorPtr_ ->
              (\(Window arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_dom_window_get_session_storage argPtr1 arg2)
                (toWindow self)
                errorPtr_))
 
getLocalStorage ::
                (MonadIO m, WindowClass self) => self -> m (Maybe Storage)
getLocalStorage self
  = liftIO
      (maybeNull (makeNewGObject mkStorage)
         (propagateGError $
            \ errorPtr_ ->
              (\(Window arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_dom_window_get_local_storage argPtr1 arg2) (toWindow self)
                errorPtr_))
getPerformance ::
               (MonadIO m, WindowClass self) => self -> m (Maybe Performance)
getPerformance self
  = liftIO
      (maybeNull (makeNewGObject mkPerformance)
         ((\(Window arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_dom_window_get_performance argPtr1) (toWindow self)))
 
getCSS :: (MonadIO m, WindowClass self) => self -> m (Maybe CSS)
getCSS self
  = liftIO
      (maybeNull (makeNewGObject mkCSS)
         ((\(Window arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_dom_window_get_css argPtr1) (toWindow self)))
 
abort :: (WindowClass self) => EventName self UIEvent
abort = EventName "abort"
 
beforeUnload :: (WindowClass self) => EventName self Event
beforeUnload = EventName "beforeunload"
 
blurEvent :: (WindowClass self) => EventName self UIEvent
blurEvent = EventName "blur"
 
canPlay :: (WindowClass self) => EventName self Event
canPlay = EventName "canplay"
 
canPlayThrough :: (WindowClass self) => EventName self Event
canPlayThrough = EventName "canplaythrough"
 
change :: (WindowClass self) => EventName self Event
change = EventName "change"
 
click :: (WindowClass self) => EventName self MouseEvent
click = EventName "click"
 
contextMenu :: (WindowClass self) => EventName self MouseEvent
contextMenu = EventName "contextmenu"
 
dblClick :: (WindowClass self) => EventName self MouseEvent
dblClick = EventName "dblclick"
 
drag :: (WindowClass self) => EventName self MouseEvent
drag = EventName "drag"
 
dragEnd :: (WindowClass self) => EventName self MouseEvent
dragEnd = EventName "dragend"
 
dragEnter :: (WindowClass self) => EventName self MouseEvent
dragEnter = EventName "dragenter"
 
dragLeave :: (WindowClass self) => EventName self MouseEvent
dragLeave = EventName "dragleave"
 
dragOver :: (WindowClass self) => EventName self MouseEvent
dragOver = EventName "dragover"
 
dragStart :: (WindowClass self) => EventName self MouseEvent
dragStart = EventName "dragstart"
 
drop :: (WindowClass self) => EventName self MouseEvent
drop = EventName "drop"
 
durationChange :: (WindowClass self) => EventName self Event
durationChange = EventName "durationchange"
 
emptied :: (WindowClass self) => EventName self Event
emptied = EventName "emptied"
 
ended :: (WindowClass self) => EventName self Event
ended = EventName "ended"
 
error :: (WindowClass self) => EventName self UIEvent
error = EventName "error"
 
focusEvent :: (WindowClass self) => EventName self UIEvent
focusEvent = EventName "focus"
 
hashChange :: (WindowClass self) => EventName self Event
hashChange = EventName "hashchange"
 
input :: (WindowClass self) => EventName self Event
input = EventName "input"
 
invalid :: (WindowClass self) => EventName self Event
invalid = EventName "invalid"
keyDown :: (WindowClass self) => EventName self KeyboardEvent
keyDown = EventName "keydown"
 
keyPress :: (WindowClass self) => EventName self KeyboardEvent
keyPress = EventName "keypress"
 
keyUp :: (WindowClass self) => EventName self KeyboardEvent
keyUp = EventName "keyup"
 
load :: (WindowClass self) => EventName self UIEvent
load = EventName "load"
 
loadedData :: (WindowClass self) => EventName self Event
loadedData = EventName "loadeddata"
 
loadedMetadata :: (WindowClass self) => EventName self Event
loadedMetadata = EventName "loadedmetadata"
 
loadStart :: (WindowClass self) => EventName self Event
loadStart = EventName "loadstart"
 
message :: (WindowClass self) => EventName self Event
message = EventName "message"
 
mouseDown :: (WindowClass self) => EventName self MouseEvent
mouseDown = EventName "mousedown"
 
mouseEnter :: (WindowClass self) => EventName self MouseEvent
mouseEnter = EventName "mouseenter"
 
mouseLeave :: (WindowClass self) => EventName self MouseEvent
mouseLeave = EventName "mouseleave"
 
mouseMove :: (WindowClass self) => EventName self MouseEvent
mouseMove = EventName "mousemove"
 
mouseOut :: (WindowClass self) => EventName self MouseEvent
mouseOut = EventName "mouseout"
 
mouseOver :: (WindowClass self) => EventName self MouseEvent
mouseOver = EventName "mouseover"
 
mouseUp :: (WindowClass self) => EventName self MouseEvent
mouseUp = EventName "mouseup"
 
mouseWheel :: (WindowClass self) => EventName self MouseEvent
mouseWheel = EventName "mousewheel"
 
offline :: (WindowClass self) => EventName self Event
offline = EventName "offline"
 
online :: (WindowClass self) => EventName self Event
online = EventName "online"
 
pageHide :: (WindowClass self) => EventName self Event
pageHide = EventName "pagehide"
 
pageShow :: (WindowClass self) => EventName self Event
pageShow = EventName "pageshow"
 
pause :: (WindowClass self) => EventName self Event
pause = EventName "pause"
 
play :: (WindowClass self) => EventName self Event
play = EventName "play"
 
playing :: (WindowClass self) => EventName self Event
playing = EventName "playing"
 
popState :: (WindowClass self) => EventName self Event
popState = EventName "popstate"
 
progress :: (WindowClass self) => EventName self Event
progress = EventName "progress"
 
rateChange :: (WindowClass self) => EventName self Event
rateChange = EventName "ratechange"
 
resize :: (WindowClass self) => EventName self UIEvent
resize = EventName "resize"
 
scrollEvent :: (WindowClass self) => EventName self UIEvent
scrollEvent = EventName "scroll"
 
seeked :: (WindowClass self) => EventName self Event
seeked = EventName "seeked"
 
seeking :: (WindowClass self) => EventName self Event
seeking = EventName "seeking"
 
select :: (WindowClass self) => EventName self UIEvent
select = EventName "select"
 
stalled :: (WindowClass self) => EventName self Event
stalled = EventName "stalled"
 
storage :: (WindowClass self) => EventName self Event
storage = EventName "storage"
 
submit :: (WindowClass self) => EventName self Event
submit = EventName "submit"
 
suspend :: (WindowClass self) => EventName self Event
suspend = EventName "suspend"
 
timeUpdate :: (WindowClass self) => EventName self Event
timeUpdate = EventName "timeupdate"
 
unload :: (WindowClass self) => EventName self UIEvent
unload = EventName "unload"
 
volumeChange :: (WindowClass self) => EventName self Event
volumeChange = EventName "volumechange"
 
waiting :: (WindowClass self) => EventName self Event
waiting = EventName "waiting"
wheel :: (WindowClass self) => EventName self WheelEvent
wheel = EventName "wheel"
 
reset :: (WindowClass self) => EventName self Event
reset = EventName "reset"
 
search :: (WindowClass self) => EventName self Event
search = EventName "search"
 
webKitAnimationEnd :: (WindowClass self) => EventName self Event
webKitAnimationEnd = EventName "webkitanimationend"
 
webKitAnimationIteration ::
                         (WindowClass self) => EventName self Event
webKitAnimationIteration = EventName "webkitanimationiteration"
 
webKitAnimationStart :: (WindowClass self) => EventName self Event
webKitAnimationStart = EventName "webkitanimationstart"
 
animationEnd :: (WindowClass self) => EventName self Event
animationEnd = EventName "animationend"
 
animationIteration :: (WindowClass self) => EventName self Event
animationIteration = EventName "animationiteration"
 
animationStart :: (WindowClass self) => EventName self Event
animationStart = EventName "animationstart"
 
webKitTransitionEnd :: (WindowClass self) => EventName self Event
webKitTransitionEnd = EventName "webkittransitionend"
 
transitionEnd :: (WindowClass self) => EventName self Event
transitionEnd = EventName "transitionend"
 
touchStart :: (WindowClass self) => EventName self UIEvent
touchStart = EventName "touchstart"
 
touchMove :: (WindowClass self) => EventName self UIEvent
touchMove = EventName "touchmove"
 
touchEnd :: (WindowClass self) => EventName self UIEvent
touchEnd = EventName "touchend"
 
touchCancel :: (WindowClass self) => EventName self UIEvent
touchCancel = EventName "touchcancel"
 
gestureStart :: (WindowClass self) => EventName self UIEvent
gestureStart = EventName "gesturestart"
 
gestureChange :: (WindowClass self) => EventName self UIEvent
gestureChange = EventName "gesturechange"
 
gestureEnd :: (WindowClass self) => EventName self UIEvent
gestureEnd = EventName "gestureend"
 
deviceMotion :: (WindowClass self) => EventName self Event
deviceMotion = EventName "devicemotion"
 
deviceOrientation :: (WindowClass self) => EventName self Event
deviceOrientation = EventName "deviceorientation"
 
webKitDeviceProximity :: (WindowClass self) => EventName self Event
webKitDeviceProximity = EventName "webkitdeviceproximity"
 
webKitWillRevealBottom ::
                       (WindowClass self) => EventName self Event
webKitWillRevealBottom = EventName "webkitwillrevealbottom"
 
webKitWillRevealLeft :: (WindowClass self) => EventName self Event
webKitWillRevealLeft = EventName "webkitwillrevealleft"
 
webKitWillRevealRight :: (WindowClass self) => EventName self Event
webKitWillRevealRight = EventName "webkitwillrevealright"
 
webKitWillRevealTop :: (WindowClass self) => EventName self Event
webKitWillRevealTop = EventName "webkitwillrevealtop"
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/Window.h webkit_dom_dom_window_get_selection"
  webkit_dom_dom_window_get_selection :: ((Ptr Window) -> (IO (Ptr Selection)))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/Window.h webkit_dom_dom_window_blur"
  webkit_dom_dom_window_blur :: ((Ptr Window) -> (IO ()))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/Window.h webkit_dom_dom_window_print"
  webkit_dom_dom_window_print :: ((Ptr Window) -> (IO ()))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/Window.h webkit_dom_dom_window_stop"
  webkit_dom_dom_window_stop :: ((Ptr Window) -> (IO ()))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/Window.h webkit_dom_dom_window_alert"
  webkit_dom_dom_window_alert :: ((Ptr Window) -> ((Ptr CChar) -> (IO ())))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/Window.h webkit_dom_dom_window_confirm"
  webkit_dom_dom_window_confirm :: ((Ptr Window) -> ((Ptr CChar) -> (IO CInt)))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/Window.h webkit_dom_dom_window_prompt"
  webkit_dom_dom_window_prompt :: ((Ptr Window) -> ((Ptr CChar) -> ((Ptr CChar) -> (IO (Ptr CChar)))))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/Window.h webkit_dom_dom_window_find"
  webkit_dom_dom_window_find :: ((Ptr Window) -> ((Ptr CChar) -> (CInt -> (CInt -> (CInt -> (CInt -> (CInt -> (CInt -> (IO CInt)))))))))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/Window.h webkit_dom_dom_window_scroll_by"
  webkit_dom_dom_window_scroll_by :: ((Ptr Window) -> (CLong -> (CLong -> (IO ()))))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/Window.h webkit_dom_dom_window_scroll_to"
  webkit_dom_dom_window_scroll_to :: ((Ptr Window) -> (CLong -> (CLong -> (IO ()))))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/Window.h webkit_dom_dom_window_scroll"
  webkit_dom_dom_window_scroll :: ((Ptr Window) -> (CLong -> (CLong -> (IO ()))))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/Window.h webkit_dom_dom_window_move_by"
  webkit_dom_dom_window_move_by :: ((Ptr Window) -> (CFloat -> (CFloat -> (IO ()))))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/Window.h webkit_dom_dom_window_move_to"
  webkit_dom_dom_window_move_to :: ((Ptr Window) -> (CFloat -> (CFloat -> (IO ()))))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/Window.h webkit_dom_dom_window_resize_by"
  webkit_dom_dom_window_resize_by :: ((Ptr Window) -> (CFloat -> (CFloat -> (IO ()))))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/Window.h webkit_dom_dom_window_resize_to"
  webkit_dom_dom_window_resize_to :: ((Ptr Window) -> (CFloat -> (CFloat -> (IO ()))))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/Window.h webkit_dom_dom_window_match_media"
  webkit_dom_dom_window_match_media :: ((Ptr Window) -> ((Ptr CChar) -> (IO (Ptr MediaQueryList))))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/Window.h webkit_dom_dom_window_get_computed_style"
  webkit_dom_dom_window_get_computed_style :: ((Ptr Window) -> ((Ptr Element) -> ((Ptr CChar) -> (IO (Ptr CSSStyleDeclaration)))))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/Window.h webkit_dom_dom_window_webkit_convert_point_from_page_to_node"
  webkit_dom_dom_window_webkit_convert_point_from_page_to_node :: ((Ptr Window) -> ((Ptr Node) -> ((Ptr WebKitPoint) -> (IO (Ptr WebKitPoint)))))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/Window.h webkit_dom_dom_window_webkit_convert_point_from_node_to_page"
  webkit_dom_dom_window_webkit_convert_point_from_node_to_page :: ((Ptr Window) -> ((Ptr Node) -> ((Ptr WebKitPoint) -> (IO (Ptr WebKitPoint)))))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/Window.h webkit_dom_dom_window_capture_events"
  webkit_dom_dom_window_capture_events :: ((Ptr Window) -> (IO ()))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/Window.h webkit_dom_dom_window_release_events"
  webkit_dom_dom_window_release_events :: ((Ptr Window) -> (IO ()))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/Window.h webkit_dom_dom_window_get_webkit_storage_info"
  webkit_dom_dom_window_get_webkit_storage_info :: ((Ptr Window) -> (IO (Ptr StorageInfo)))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/Window.h webkit_dom_dom_window_get_screen"
  webkit_dom_dom_window_get_screen :: ((Ptr Window) -> (IO (Ptr Screen)))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/Window.h webkit_dom_dom_window_get_history"
  webkit_dom_dom_window_get_history :: ((Ptr Window) -> (IO (Ptr History)))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/Window.h webkit_dom_dom_window_get_locationbar"
  webkit_dom_dom_window_get_locationbar :: ((Ptr Window) -> (IO (Ptr BarProp)))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/Window.h webkit_dom_dom_window_get_menubar"
  webkit_dom_dom_window_get_menubar :: ((Ptr Window) -> (IO (Ptr BarProp)))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/Window.h webkit_dom_dom_window_get_personalbar"
  webkit_dom_dom_window_get_personalbar :: ((Ptr Window) -> (IO (Ptr BarProp)))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/Window.h webkit_dom_dom_window_get_scrollbars"
  webkit_dom_dom_window_get_scrollbars :: ((Ptr Window) -> (IO (Ptr BarProp)))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/Window.h webkit_dom_dom_window_get_statusbar"
  webkit_dom_dom_window_get_statusbar :: ((Ptr Window) -> (IO (Ptr BarProp)))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/Window.h webkit_dom_dom_window_get_toolbar"
  webkit_dom_dom_window_get_toolbar :: ((Ptr Window) -> (IO (Ptr BarProp)))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/Window.h webkit_dom_dom_window_get_navigator"
  webkit_dom_dom_window_get_navigator :: ((Ptr Window) -> (IO (Ptr Navigator)))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/Window.h webkit_dom_dom_window_get_client_information"
  webkit_dom_dom_window_get_client_information :: ((Ptr Window) -> (IO (Ptr Navigator)))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/Window.h webkit_dom_dom_window_get_frame_element"
  webkit_dom_dom_window_get_frame_element :: ((Ptr Window) -> (IO (Ptr Element)))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/Window.h webkit_dom_dom_window_get_offscreen_buffering"
  webkit_dom_dom_window_get_offscreen_buffering :: ((Ptr Window) -> (IO CInt))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/Window.h webkit_dom_dom_window_get_outer_height"
  webkit_dom_dom_window_get_outer_height :: ((Ptr Window) -> (IO CLong))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/Window.h webkit_dom_dom_window_get_outer_width"
  webkit_dom_dom_window_get_outer_width :: ((Ptr Window) -> (IO CLong))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/Window.h webkit_dom_dom_window_get_inner_height"
  webkit_dom_dom_window_get_inner_height :: ((Ptr Window) -> (IO CLong))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/Window.h webkit_dom_dom_window_get_inner_width"
  webkit_dom_dom_window_get_inner_width :: ((Ptr Window) -> (IO CLong))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/Window.h webkit_dom_dom_window_get_screen_x"
  webkit_dom_dom_window_get_screen_x :: ((Ptr Window) -> (IO CLong))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/Window.h webkit_dom_dom_window_get_screen_y"
  webkit_dom_dom_window_get_screen_y :: ((Ptr Window) -> (IO CLong))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/Window.h webkit_dom_dom_window_get_screen_left"
  webkit_dom_dom_window_get_screen_left :: ((Ptr Window) -> (IO CLong))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/Window.h webkit_dom_dom_window_get_screen_top"
  webkit_dom_dom_window_get_screen_top :: ((Ptr Window) -> (IO CLong))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/Window.h webkit_dom_dom_window_get_scroll_x"
  webkit_dom_dom_window_get_scroll_x :: ((Ptr Window) -> (IO CLong))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/Window.h webkit_dom_dom_window_get_scroll_y"
  webkit_dom_dom_window_get_scroll_y :: ((Ptr Window) -> (IO CLong))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/Window.h webkit_dom_dom_window_get_page_x_offset"
  webkit_dom_dom_window_get_page_x_offset :: ((Ptr Window) -> (IO CLong))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/Window.h webkit_dom_dom_window_get_page_y_offset"
  webkit_dom_dom_window_get_page_y_offset :: ((Ptr Window) -> (IO CLong))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/Window.h webkit_dom_dom_window_get_closed"
  webkit_dom_dom_window_get_closed :: ((Ptr Window) -> (IO CInt))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/Window.h webkit_dom_dom_window_get_length"
  webkit_dom_dom_window_get_length :: ((Ptr Window) -> (IO CULong))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/Window.h webkit_dom_dom_window_set_name"
  webkit_dom_dom_window_set_name :: ((Ptr Window) -> ((Ptr CChar) -> (IO ())))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/Window.h webkit_dom_dom_window_get_name"
  webkit_dom_dom_window_get_name :: ((Ptr Window) -> (IO (Ptr CChar)))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/Window.h webkit_dom_dom_window_set_status"
  webkit_dom_dom_window_set_status :: ((Ptr Window) -> ((Ptr CChar) -> (IO ())))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/Window.h webkit_dom_dom_window_get_status"
  webkit_dom_dom_window_get_status :: ((Ptr Window) -> (IO (Ptr CChar)))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/Window.h webkit_dom_dom_window_set_default_status"
  webkit_dom_dom_window_set_default_status :: ((Ptr Window) -> ((Ptr CChar) -> (IO ())))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/Window.h webkit_dom_dom_window_get_default_status"
  webkit_dom_dom_window_get_default_status :: ((Ptr Window) -> (IO (Ptr CChar)))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/Window.h webkit_dom_dom_window_get_self"
  webkit_dom_dom_window_get_self :: ((Ptr Window) -> (IO (Ptr Window)))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/Window.h webkit_dom_dom_window_get_window"
  webkit_dom_dom_window_get_window :: ((Ptr Window) -> (IO (Ptr Window)))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/Window.h webkit_dom_dom_window_get_frames"
  webkit_dom_dom_window_get_frames :: ((Ptr Window) -> (IO (Ptr Window)))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/Window.h webkit_dom_dom_window_get_opener"
  webkit_dom_dom_window_get_opener :: ((Ptr Window) -> (IO (Ptr Window)))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/Window.h webkit_dom_dom_window_get_parent"
  webkit_dom_dom_window_get_parent :: ((Ptr Window) -> (IO (Ptr Window)))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/Window.h webkit_dom_dom_window_get_top"
  webkit_dom_dom_window_get_top :: ((Ptr Window) -> (IO (Ptr Window)))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/Window.h webkit_dom_dom_window_get_document"
  webkit_dom_dom_window_get_document :: ((Ptr Window) -> (IO (Ptr Document)))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/Window.h webkit_dom_dom_window_get_style_media"
  webkit_dom_dom_window_get_style_media :: ((Ptr Window) -> (IO (Ptr StyleMedia)))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/Window.h webkit_dom_dom_window_get_device_pixel_ratio"
  webkit_dom_dom_window_get_device_pixel_ratio :: ((Ptr Window) -> (IO CDouble))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/Window.h webkit_dom_dom_window_get_application_cache"
  webkit_dom_dom_window_get_application_cache :: ((Ptr Window) -> (IO (Ptr ApplicationCache)))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/Window.h webkit_dom_dom_window_get_session_storage"
  webkit_dom_dom_window_get_session_storage :: ((Ptr Window) -> ((Ptr (Ptr ())) -> (IO (Ptr Storage))))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/Window.h webkit_dom_dom_window_get_local_storage"
  webkit_dom_dom_window_get_local_storage :: ((Ptr Window) -> ((Ptr (Ptr ())) -> (IO (Ptr Storage))))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/Window.h webkit_dom_dom_window_get_performance"
  webkit_dom_dom_window_get_performance :: ((Ptr Window) -> (IO (Ptr Performance)))
foreign import ccall safe "dist/build/Graphics/UI/Gtk/WebKit/DOM/Window.h webkit_dom_dom_window_get_css"
  webkit_dom_dom_window_get_css :: ((Ptr Window) -> (IO (Ptr CSS)))