module Graphics.UI.Gtk.WebKit.WebView (
  WebView,
  WebViewClass,
  NavigationResponse(..),
  TargetInfo(..),
  LoadStatus(..),
  ViewMode(..),
  webViewNew,
  webViewLoadUri,
  webViewLoadHtmlString,
  webViewLoadRequest,
  webViewLoadString,
  webViewGetLoadStatus,
  webViewStopLoading,
  webViewReload,
  webViewReloadBypassCache,
  webViewCanGoBack,
  webViewCanGoForward,
  webViewGoBack,
  webViewGoForward,
  webViewGetBackForwardList,
  webViewSetMaintainsBackForwardList,
  webViewGoToBackForwardItem,
  webViewCanGoBackOrForward,
  webViewGoBackOrForward,
  webViewGetZoomLevel,
  webViewSetZoomLevel,
  webViewZoomIn,
  webViewZoomOut,
  webViewGetFullContentZoom,
  webViewSetFullContentZoom,
  webViewCanCutClipboard,
  webViewCanCopyClipboard,
  webViewCanPasteClipboard,
  webViewCutClipboard,
  webViewCopyClipboard,
  webViewPasteClipboard,
  webViewCanRedo,
  webViewCanUndo,
  webViewRedo,
  webViewUndo,
  webViewDeleteSelection,
  webViewHasSelection,
  webViewSelectAll,
  webViewGetEncoding,
  webViewSetCustomEncoding,
  webViewGetCustomEncoding,
  webViewGetViewMode,
  webViewSetViewMode,
  webViewGetViewSourceMode,
  webViewSetViewSourceMode,
  webViewGetTransparent,
  webViewSetTransparent,
  webViewGetCopyTargetList,
  webViewGetPasteTargetList,
  webViewMarkTextMatches,
  webViewUnMarkTextMatches,
  webViewSetHighlightTextMatches,
  webViewGetIconUri,
  webViewTryGetFaviconPixbuf,
  webViewExecuteScript,
  webViewCanShowMimeType,
  webViewGetEditable,
  webViewSetEditable,
  webViewGetInspector,
  webViewGetProgress,
  webViewSearchText,
  webViewMoveCursor,
  webViewGetMainFrame,
  webViewGetFocusedFrame,
  webViewSetWebSettings,
  webViewGetWebSettings,
  webViewGetWindowFeatures,
  webViewGetTitle,
  webViewGetUri,
  webViewGetDomDocument,
  
  
  webViewZoomLevel,
  webViewFullContentZoom,
  webViewEncoding,
  webViewCustomEncoding,
  webViewLoadStatus,
  webViewProgress,
  webViewTitle,
  webViewInspector,
  webViewWebSettings,
  webViewViewSourceMode,
  webViewTransparent,
  webViewEditable,
  webViewUri,
  webViewCopyTargetList,
  webViewPasteTargetList,
  webViewWindowFeatures,
  webViewIconUri,
  webViewImContext,
  webViewViewMode,
  loadStarted,
  loadCommitted,
  progressChanged,
  loadFinished,
  loadError,
  iconLoaded,
  documentLoadFinished,
  resourceRequestStarting,
  titleChanged,
  copyClipboard,
  cutClipboard,
  pasteClipboard,
  consoleMessage,
  scriptAlert,
  scriptConfirm,
  scriptPrompt,
  statusBarTextChanged,
  populatePopup,
  editingBegan,
  editingEnded,
  selectAll,
  selectionChanged,
  mimeTypePolicyDecisionRequested,
  navigationPolicyDecisionRequested,
  newWindowPolicyDecisionRequested,
  geolocationPolicyDecisionCancelled,
  geolocationPolicyDecisionRequested,
  
  moveCursor,
  setScrollAdjustments,
  hoveringOverLink,
  createWebView,
  webViewReady,
  closeWebView,
  printRequested,
  databaseQuotaExceeded,
  downloadRequested,
  redo,
  undo,
) where
import Control.Monad (liftM, (<=<))
import Data.ByteString (ByteString, useAsCString)
import System.Glib.FFI
import System.Glib.UTFString
import System.Glib.GList
import System.Glib.Attributes as G
import System.Glib.Properties
import System.Glib.GError
import Graphics.UI.Gtk.Gdk.Events
import Graphics.UI.Gtk.Abstract.Object (makeNewObject)
import Graphics.UI.Gtk.WebKit.Types
import Graphics.UI.Gtk.WebKit.Signals
import Graphics.UI.Gtk.WebKit.Internal
import System.Glib.GObject
import Graphics.UI.Gtk.General.Selection ( TargetList )
import Graphics.UI.Gtk.MenuComboToolbar.Menu
import Graphics.UI.Gtk.General.Enums
data NavigationResponse = NavigationResponseAccept
                        | NavigationResponseIgnore
                        | NavigationResponseDownload
                        deriving (Enum,Eq,Show)
data TargetInfo = WebViewTargetInfoHtml
                | WebViewTargetInfoText
                | WebViewTargetInfoImage
                | WebViewTargetInfoUriList
                | WebViewTargetInfoNetscapeUrl
                deriving (Enum,Eq,Show)
data ViewMode = WebViewViewModeWindowed
              | WebViewViewModeFloating
              | WebViewViewModeFullscreen
              | WebViewViewModeMaximized
              | WebViewViewModeMinimized
              deriving (Enum,Eq,Show)
data LoadStatus = LoadProvisional
                | LoadCommitted
                | LoadFinished
                | LoadFirstVisuallyNonEmptyLayout
                | LoadFailed
                deriving (Enum,Eq,Show)
webViewNew :: IO WebView
webViewNew = do
  isGthreadInited <- liftM toBool g_thread_get_initialized
  if not isGthreadInited then g_thread_init nullPtr
    else return ()
  makeNewObject mkWebView $ liftM castPtr webkit_web_view_new
webViewSetWebSettings :: (WebViewClass self, WebSettingsClass settings) => self -> settings -> IO ()
webViewSetWebSettings webview websettings =
    (\(WebView arg1) (WebSettings arg2) -> withForeignPtr arg1 $ \argPtr1 ->withForeignPtr arg2 $ \argPtr2 ->webkit_web_view_set_settings argPtr1 argPtr2) (toWebView webview) (toWebSettings websettings)
webViewGetWebSettings :: WebViewClass self => self -> IO WebSettings
webViewGetWebSettings = makeNewGObject mkWebSettings . (\(WebView arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_web_view_get_settings argPtr1) . toWebView
webViewGetWindowFeatures :: WebViewClass self => self -> IO WebWindowFeatures
webViewGetWindowFeatures = makeNewGObject mkWebWindowFeatures . (\(WebView arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_web_view_get_window_features argPtr1) . toWebView
webViewGetIconUri :: (WebViewClass self, GlibString string) => self -> IO (Maybe string)
webViewGetIconUri webview =
  (\(WebView arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_web_view_get_icon_uri argPtr1) (toWebView webview)
  >>= maybePeek peekUTFString
webViewTryGetFaviconPixbuf ::
    WebView
    -> Int 
    -> Int 
    -> IO (Maybe Pixbuf) 
webViewTryGetFaviconPixbuf webView width length = do
    faviconPtr <- (\(WebView arg1) arg2 arg3 -> withForeignPtr arg1 $ \argPtr1 ->webkit_web_view_try_get_favicon_pixbuf argPtr1 arg2 arg3) webView (fromIntegral width) (fromIntegral length)
    if faviconPtr == nullPtr then return Nothing else liftM Just . makeNewGObject mkPixbuf $ return faviconPtr
webViewGetMainFrame :: WebViewClass self => self -> IO WebFrame
webViewGetMainFrame = makeNewGObject mkWebFrame . (\(WebView arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_web_view_get_main_frame argPtr1) . toWebView
webViewGetFocusedFrame :: WebViewClass self => self -> IO (Maybe WebFrame)
webViewGetFocusedFrame webView = do
    framePtr <- (\(WebView arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_web_view_get_focused_frame argPtr1) $ toWebView webView
    if framePtr == nullPtr then return Nothing else liftM Just . makeNewGObject mkWebFrame $ return framePtr
webViewLoadUri :: (WebViewClass self, GlibString string) => self -> string -> IO ()
webViewLoadUri webview url = withUTFString url $ (\(WebView arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->webkit_web_view_load_uri argPtr1 arg2) (toWebView webview)
webViewCanGoBack ::
    WebViewClass self => self
 -> IO Bool 
webViewCanGoBack webview =
    liftM toBool $ (\(WebView arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_web_view_can_go_back argPtr1) (toWebView webview)
webViewCanGoForward ::
    WebViewClass self => self
 -> IO Bool 
webViewCanGoForward webview =
    liftM toBool $ (\(WebView arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_web_view_can_go_forward argPtr1) (toWebView webview)
webViewGoBack :: WebViewClass self => self -> IO ()
webViewGoBack = (\(WebView arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_web_view_go_back argPtr1) . toWebView
webViewGoForward :: WebViewClass self => self -> IO ()
webViewGoForward = (\(WebView arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_web_view_go_forward argPtr1) . toWebView
webViewSetMaintainsBackForwardList :: WebViewClass self => self
 -> Bool 
 -> IO()
webViewSetMaintainsBackForwardList webview flag =
    (\(WebView arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->webkit_web_view_set_maintains_back_forward_list argPtr1 arg2) (toWebView webview) (fromBool flag)
webViewGetBackForwardList ::
    WebViewClass self => self
 -> IO WebBackForwardList
webViewGetBackForwardList webview =
    makeNewGObject mkWebBackForwardList $
      (\(WebView arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_web_view_get_back_forward_list argPtr1)
        (toWebView webview)
webViewGoToBackForwardItem :: (WebViewClass self, WebHistoryItemClass item) => self
    -> item
    -> IO Bool 
webViewGoToBackForwardItem webview item =
    liftM toBool $ (\(WebView arg1) (WebHistoryItem arg2) -> withForeignPtr arg1 $ \argPtr1 ->withForeignPtr arg2 $ \argPtr2 ->webkit_web_view_go_to_back_forward_item argPtr1 argPtr2) (toWebView webview) (toWebHistoryItem item)
webViewCanGoBackOrForward :: WebViewClass self => self
    -> Int 
    -> IO Bool 
webViewCanGoBackOrForward webview steps =
    liftM toBool $
      (\(WebView arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->webkit_web_view_can_go_back_or_forward argPtr1 arg2)
        (toWebView webview)
        (fromIntegral steps)
webViewGoBackOrForward :: WebViewClass self => self -> Int -> IO ()
webViewGoBackOrForward webview steps = (\(WebView arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->webkit_web_view_go_back_or_forward argPtr1 arg2) (toWebView webview) (fromIntegral steps)
webViewCanRedo :: WebViewClass self => self -> IO Bool
webViewCanRedo = liftM toBool . (\(WebView arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_web_view_can_redo argPtr1) . toWebView
webViewCanUndo :: WebViewClass self => self -> IO Bool
webViewCanUndo = liftM toBool . (\(WebView arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_web_view_can_undo argPtr1) . toWebView
webViewRedo :: WebViewClass self => self -> IO ()
webViewRedo = (\(WebView arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_web_view_redo argPtr1) . toWebView
webViewUndo :: WebViewClass self => self -> IO ()
webViewUndo = (\(WebView arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_web_view_undo argPtr1) . toWebView
webViewCanShowMimeType :: (WebViewClass self, GlibString string) => self
    -> string 
    -> IO Bool 
webViewCanShowMimeType webview mime = withUTFString mime $ liftM toBool . (\(WebView arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->webkit_web_view_can_show_mime_type argPtr1 arg2) (toWebView webview)
webViewGetEditable :: WebViewClass self => self -> IO Bool
webViewGetEditable = liftM toBool . (\(WebView arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_web_view_get_editable argPtr1) . toWebView
webViewSetEditable :: WebViewClass self => self -> Bool -> IO ()
webViewSetEditable webview editable = (\(WebView arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->webkit_web_view_set_editable argPtr1 arg2) (toWebView webview) (fromBool editable)
webViewGetViewMode :: WebViewClass self => self -> IO ViewMode
webViewGetViewMode = liftM (toEnum . fromIntegral) . (\(WebView arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_web_view_get_view_source_mode argPtr1) . toWebView
webViewSetViewMode :: WebViewClass self => self -> ViewMode -> IO ()
webViewSetViewMode (toWebView -> webView) viewMode = (\(WebView arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->webkit_web_view_set_view_source_mode argPtr1 arg2) webView (fromIntegral . fromEnum $ viewMode)
webViewGetViewSourceMode :: WebViewClass self => self -> IO Bool
webViewGetViewSourceMode = liftM toBool . (\(WebView arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_web_view_get_view_source_mode argPtr1) . toWebView
webViewSetViewSourceMode :: WebViewClass self => self -> Bool -> IO ()
webViewSetViewSourceMode webview mode =
    (\(WebView arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->webkit_web_view_set_view_source_mode argPtr1 arg2) (toWebView webview) (fromBool mode)
webViewGetTransparent :: WebViewClass self => self -> IO Bool
webViewGetTransparent = liftM toBool . (\(WebView arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_web_view_get_transparent argPtr1) . toWebView
webViewSetTransparent :: WebViewClass self => self -> Bool -> IO ()
webViewSetTransparent webview trans =
    (\(WebView arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->webkit_web_view_set_transparent argPtr1 arg2) (toWebView webview) (fromBool trans)
webViewGetInspector :: WebViewClass self => self -> IO WebInspector
webViewGetInspector = makeNewGObject mkWebInspector . (\(WebView arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_web_view_get_inspector argPtr1) . toWebView
webViewLoadRequest :: (WebViewClass self, NetworkRequestClass request) => self -> request -> IO()
webViewLoadRequest webview request = (\(WebView arg1) (NetworkRequest arg2) -> withForeignPtr arg1 $ \argPtr1 ->withForeignPtr arg2 $ \argPtr2 ->webkit_web_view_load_request argPtr1 argPtr2) (toWebView webview) (toNetworkRequest request)
webViewGetZoomLevel :: WebViewClass self => self -> IO Float
webViewGetZoomLevel = liftM realToFrac . (\(WebView arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_web_view_get_zoom_level argPtr1) . toWebView
webViewSetZoomLevel :: WebViewClass self => self
 -> Float 
 -> IO ()
webViewSetZoomLevel webview zlevel =
    (\(WebView arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->webkit_web_view_set_zoom_level argPtr1 arg2) (toWebView webview) (realToFrac zlevel)
webViewLoadHtmlString :: (WebViewClass self, GlibString string) => self
    -> string 
    -> string 
    -> IO()
webViewLoadHtmlString webview htmlstr url = withUTFString htmlstr $ \htmlPtr -> withUTFString url $ \urlPtr ->
    (\(WebView arg1) arg2 arg3 -> withForeignPtr arg1 $ \argPtr1 ->webkit_web_view_load_html_string argPtr1 arg2 arg3) (toWebView webview) htmlPtr urlPtr
webViewLoadString :: (WebViewClass self, GlibString string) => self
    -> string 
    -> (Maybe string) 
    -> string 
    -> IO ()
webViewLoadString webview content mimetype baseuri =
    withUTFString content $ \contentPtr ->
    maybeWith withUTFString mimetype $ \mimetypePtr ->
    withUTFString baseuri $ \baseuriPtr ->
        (\(WebView arg1) arg2 arg3 arg4 arg5 -> withForeignPtr arg1 $ \argPtr1 ->webkit_web_view_load_string argPtr1 arg2 arg3 arg4 arg5)
          (toWebView webview)
          contentPtr
          mimetypePtr
          nullPtr
          baseuriPtr
webViewLoadByteString :: (WebViewClass self, GlibString string) => self
    -> ByteString 
    -> (Maybe string) 
    -> (Maybe string) 
    -> string 
    -> IO ()
webViewLoadByteString webview content mimetype encoding baseuri =
    useAsCString content $ \contentPtr ->
    maybeWith withUTFString mimetype $ \mimetypePtr ->
    maybeWith withUTFString encoding $ \encodingPtr ->
    withUTFString baseuri $ \baseuriPtr ->
        (\(WebView arg1) arg2 arg3 arg4 arg5 -> withForeignPtr arg1 $ \argPtr1 ->webkit_web_view_load_string argPtr1 arg2 arg3 arg4 arg5)
          (toWebView webview)
          contentPtr
          mimetypePtr
          encodingPtr
          baseuriPtr
webViewGetTitle :: (WebViewClass self, GlibString string) => self -> IO (Maybe string)
webViewGetTitle = maybePeek peekUTFString <=< (\(WebView arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_web_view_get_title argPtr1) . toWebView
webViewGetUri :: (WebViewClass self, GlibString string) => self -> IO (Maybe string)
webViewGetUri = maybePeek peekUTFString <=< (\(WebView arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_web_view_get_uri argPtr1) . toWebView
webViewStopLoading :: WebViewClass self => self -> IO ()
webViewStopLoading = (\(WebView arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_web_view_stop_loading argPtr1) . toWebView
webViewReload :: WebViewClass self => self -> IO ()
webViewReload = (\(WebView arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_web_view_reload argPtr1) . toWebView
webViewReloadBypassCache :: WebViewClass self => self -> IO ()
webViewReloadBypassCache = (\(WebView arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_web_view_reload_bypass_cache argPtr1) . toWebView
webViewZoomIn :: WebViewClass self => self -> IO()
webViewZoomIn = (\(WebView arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_web_view_zoom_in argPtr1) . toWebView
webViewZoomOut :: WebViewClass self => self -> IO ()
webViewZoomOut = (\(WebView arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_web_view_zoom_out argPtr1) . toWebView
webViewSearchText :: (WebViewClass self, GlibString string) => self
 -> string 
 -> Bool 
 -> Bool 
 -> Bool 
 -> IO Bool 
webViewSearchText webview text case_sensitive forward wrap =
    withUTFString text $ \textPtr ->
        liftM toBool $
          (\(WebView arg1) arg2 arg3 arg4 arg5 -> withForeignPtr arg1 $ \argPtr1 ->webkit_web_view_search_text argPtr1 arg2 arg3 arg4 arg5)
            (toWebView webview)
            textPtr
            (fromBool case_sensitive)
            (fromBool forward)
            (fromBool wrap)
webViewMarkTextMatches :: (WebViewClass self, GlibString string) => self
 -> string 
 -> Bool 
 -> Int 
 -> IO Int 
webViewMarkTextMatches webview text case_sensitive limit = withUTFString text $ \textPtr -> liftM fromIntegral $
    (\(WebView arg1) arg2 arg3 arg4 -> withForeignPtr arg1 $ \argPtr1 ->webkit_web_view_mark_text_matches argPtr1 arg2 arg3 arg4) (toWebView webview) textPtr (fromBool case_sensitive) (fromIntegral limit)
webViewMoveCursor :: WebViewClass self => self -> MovementStep -> Int -> IO ()
webViewMoveCursor webview step count =
    (\(WebView arg1) arg2 arg3 -> withForeignPtr arg1 $ \argPtr1 ->webkit_web_view_move_cursor argPtr1 arg2 arg3) (toWebView webview) (fromIntegral $ fromEnum step) (fromIntegral count)
webViewUnMarkTextMatches :: WebViewClass self => self -> IO ()
webViewUnMarkTextMatches = (\(WebView arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_web_view_unmark_text_matches argPtr1) . toWebView
webViewSetHighlightTextMatches :: WebViewClass self => self
 -> Bool 
 -> IO ()
webViewSetHighlightTextMatches webview highlight =
    (\(WebView arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->webkit_web_view_set_highlight_text_matches argPtr1 arg2) (toWebView webview) (fromBool highlight)
webViewExecuteScript :: (WebViewClass self, GlibString string) => self
    -> string 
    -> IO()
webViewExecuteScript webview script = withUTFString script $ (\(WebView arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->webkit_web_view_execute_script argPtr1 arg2) (toWebView webview)
webViewCanCutClipboard :: WebViewClass self => self -> IO Bool
webViewCanCutClipboard = liftM toBool . (\(WebView arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_web_view_can_cut_clipboard argPtr1) . toWebView
webViewCanCopyClipboard :: WebViewClass self => self -> IO Bool
webViewCanCopyClipboard webview =
    liftM toBool $ (\(WebView arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_web_view_can_copy_clipboard argPtr1) (toWebView webview)
webViewCanPasteClipboard :: WebViewClass self => self -> IO Bool
webViewCanPasteClipboard webview =
    liftM toBool $ (\(WebView arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_web_view_can_paste_clipboard argPtr1) (toWebView webview)
webViewCutClipboard :: WebViewClass self => self -> IO()
webViewCutClipboard webview =
    (\(WebView arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_web_view_cut_clipboard argPtr1) (toWebView webview)
webViewCopyClipboard :: WebViewClass self => self -> IO()
webViewCopyClipboard webview =
    (\(WebView arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_web_view_copy_clipboard argPtr1) (toWebView webview)
webViewPasteClipboard :: WebViewClass self => self -> IO ()
webViewPasteClipboard = (\(WebView arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_web_view_paste_clipboard argPtr1) . toWebView
webViewDeleteSelection :: WebViewClass self => self -> IO ()
webViewDeleteSelection = (\(WebView arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_web_view_delete_selection argPtr1) . toWebView
webViewHasSelection :: WebViewClass self => self -> IO Bool
webViewHasSelection = liftM toBool . (\(WebView arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_web_view_has_selection argPtr1) . toWebView
webViewSelectAll :: WebViewClass self => self -> IO ()
webViewSelectAll = (\(WebView arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_web_view_select_all argPtr1) . toWebView
webViewGetFullContentZoom :: WebViewClass self => self
    -> IO Bool 
               
webViewGetFullContentZoom = liftM toBool . (\(WebView arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_web_view_get_full_content_zoom argPtr1) . toWebView
webViewSetFullContentZoom :: WebViewClass self => self
 -> Bool 
         
 -> IO ()
webViewSetFullContentZoom webview full =
    (\(WebView arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->webkit_web_view_set_full_content_zoom argPtr1 arg2) (toWebView webview) (fromBool full)
webViewGetEncoding :: (WebViewClass self, GlibString string) => self
    -> IO (Maybe string) 
webViewGetEncoding webview = (\(WebView arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_web_view_get_encoding argPtr1) (toWebView webview) >>= maybePeek peekUTFString
webViewSetCustomEncoding :: (WebViewClass self, GlibString string) => self
    -> (Maybe string) 
    -> IO ()
webViewSetCustomEncoding webview encoding =
    maybeWith withUTFString encoding $ \encodingPtr ->
        (\(WebView arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->webkit_web_view_set_custom_encoding argPtr1 arg2) (toWebView webview) encodingPtr
webViewGetCustomEncoding :: (WebViewClass self, GlibString string) => self
    -> IO (Maybe string) 
webViewGetCustomEncoding = maybePeek peekUTFString <=< (\(WebView arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_web_view_get_custom_encoding argPtr1) . toWebView
webViewGetLoadStatus :: WebViewClass self => self -> IO LoadStatus
webViewGetLoadStatus = liftM (toEnum . fromIntegral) . (\(WebView arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_web_view_get_load_status argPtr1) . toWebView
webViewGetProgress :: WebViewClass self => self
    -> IO Double 
webViewGetProgress = liftM realToFrac . (\(WebView arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_web_view_get_progress argPtr1) . toWebView
webViewGetCopyTargetList :: WebViewClass self => self -> IO (Maybe TargetList)
webViewGetCopyTargetList webview = do
  tlPtr <- (\(WebView arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_web_view_get_copy_target_list argPtr1) (toWebView webview)
  if tlPtr == nullPtr then return Nothing else liftM Just (mkTargetList tlPtr)
webViewGetPasteTargetList :: WebViewClass self => self -> IO (Maybe TargetList)
webViewGetPasteTargetList = maybePeek mkTargetList <=< (\(WebView arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_web_view_get_paste_target_list argPtr1) . toWebView
webViewZoomLevel :: WebViewClass self => G.Attr self Float
webViewZoomLevel = newAttrFromFloatProperty "zoom-level"
webViewFullContentZoom :: WebViewClass self => G.Attr self Bool
webViewFullContentZoom = newAttrFromBoolProperty "full-content-zoom"
webViewEncoding :: (WebViewClass self, GlibString string) => ReadAttr self (Maybe string)
webViewEncoding = readAttrFromMaybeStringProperty "encoding"
webViewLoadStatus :: WebViewClass self => ReadAttr self LoadStatus
webViewLoadStatus = readAttrFromEnumProperty "load-status" webkit_load_status_get_type
webViewProgress :: WebViewClass self => ReadAttr self Double
webViewProgress = readAttrFromDoubleProperty "progress"
webViewWebSettings :: WebViewClass self => G.Attr self WebSettings
webViewWebSettings = newAttr
   webViewGetWebSettings
   webViewSetWebSettings
webViewTitle :: (WebViewClass self, GlibString string) => ReadAttr self (Maybe string)
webViewTitle = readAttrFromMaybeStringProperty "title"
webViewInspector :: WebViewClass self => ReadAttr self WebInspector
webViewInspector = readAttr webViewGetInspector
webViewCustomEncoding :: (WebViewClass self, GlibString string) => G.Attr self (Maybe string)
webViewCustomEncoding = newAttrFromMaybeStringProperty "custom-encoding"
webViewViewSourceMode :: WebViewClass self => G.Attr self Bool
webViewViewSourceMode = newAttr
  webViewGetViewSourceMode
  webViewSetViewSourceMode
webViewTransparent :: WebViewClass self => G.Attr self Bool
webViewTransparent = newAttrFromBoolProperty "transparent"
webViewEditable :: WebViewClass self => G.Attr self Bool
webViewEditable = newAttrFromBoolProperty "editable"
webViewUri :: (WebViewClass self, GlibString string) => ReadAttr self (Maybe string)
webViewUri = readAttrFromMaybeStringProperty "uri"
webViewCopyTargetList :: WebViewClass self => ReadAttr self (Maybe TargetList)
webViewCopyTargetList = readAttr webViewGetCopyTargetList
webViewPasteTargetList :: WebViewClass self => ReadAttr self (Maybe TargetList)
webViewPasteTargetList = readAttr webViewGetPasteTargetList
webViewWindowFeatures :: WebViewClass self => G.Attr self WebWindowFeatures
webViewWindowFeatures =
  newAttrFromObjectProperty "window-features"
  webkit_web_window_features_get_type
webViewIconUri :: (WebViewClass self, GlibString string) => ReadAttr self (Maybe string)
webViewIconUri = readAttrFromMaybeStringProperty "icon-uri"
webViewImContext :: WebViewClass self => ReadAttr self IMContext
webViewImContext =
  readAttrFromObjectProperty "im-context"
  gtk_im_context_get_type
webViewViewMode :: (WebViewClass self) => G.Attr self ViewMode
webViewViewMode = newAttr
    webViewGetViewMode
    webViewSetViewMode
webViewGetDomDocument :: WebView -> IO (Maybe Document)
webViewGetDomDocument webView = do
    docPtr <- (\(WebView arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_web_view_get_dom_document argPtr1) webView
    if docPtr == nullPtr then return Nothing else liftM Just . makeNewGObject mkDocument $ return docPtr
titleChanged :: (WebViewClass self, GlibString string) => Signal self ( WebFrame -> string -> IO() )
titleChanged = Signal (connect_OBJECT_GLIBSTRING__NONE "title_changed")
hoveringOverLink :: (WebViewClass self, GlibString string) => Signal self (Maybe string -> Maybe string -> IO())
hoveringOverLink = Signal (connect_MGLIBSTRING_MGLIBSTRING__NONE "hovering_over_link")
loadStarted :: WebViewClass self => Signal self (WebFrame -> IO())
loadStarted = Signal (connect_OBJECT__NONE "load_started")
loadCommitted :: WebViewClass self => Signal self (WebFrame -> IO())
loadCommitted = Signal (connect_OBJECT__NONE "load_committed")
progressChanged :: WebViewClass self => Signal self (Int-> IO())
progressChanged = Signal (connect_INT__NONE "load_progress_changed")
loadFinished :: WebViewClass self => Signal self (WebFrame -> IO())
loadFinished = Signal (connect_OBJECT__NONE "load_finished")
loadError :: (WebViewClass self, GlibString string) => Signal self (WebFrame -> string -> GError -> IO Bool)
loadError = Signal (connect_OBJECT_GLIBSTRING_BOXED__BOOL "load_error" peek)
createWebView :: WebViewClass self => Signal self (WebFrame -> IO WebView)
createWebView = Signal (connect_OBJECT__OBJECTPTR "create_web_view")
closeWebView :: WebViewClass self => Signal self (IO Bool)
closeWebView = Signal (connect_NONE__BOOL "close_web_view")
consoleMessage :: (WebViewClass self, GlibString string) => Signal self (string -> string -> Int -> string -> IO Bool)
consoleMessage = Signal (connect_GLIBSTRING_GLIBSTRING_INT_GLIBSTRING__BOOL "console_message")
copyClipboard :: WebViewClass self => Signal self (IO ())
copyClipboard = Signal (connect_NONE__NONE "copy_clipboard")
cutClipboard :: WebViewClass self => Signal self (IO ())
cutClipboard = Signal (connect_NONE__NONE "cut_clipboard")
pasteClipboard :: WebViewClass self => Signal self (IO ())
pasteClipboard = Signal (connect_NONE__NONE "paste_clipboard")
populatePopup :: WebViewClass self => Signal self (Menu -> IO ())
populatePopup = Signal (connect_OBJECT__NONE "populate_popup")
printRequested :: WebViewClass self => Signal self (WebFrame -> IO Bool)
printRequested = Signal (connect_OBJECT__BOOL "print_requested")
scriptAlert :: (WebViewClass self, GlibString string) => Signal self (WebFrame -> string -> IO Bool)
scriptAlert = Signal (connect_OBJECT_GLIBSTRING__BOOL "script_alert")
scriptConfirm :: (WebViewClass self, GlibString string) => Signal self (WebFrame -> string -> IO Bool)
scriptConfirm = Signal (connect_OBJECT_GLIBSTRING__BOOL "script_confirm")
scriptPrompt :: (WebViewClass self, GlibString string) => Signal self (WebFrame -> string -> string -> IO Bool)
scriptPrompt = Signal (connect_OBJECT_GLIBSTRING_GLIBSTRING__BOOL "script_prompt")
statusBarTextChanged :: (WebViewClass self, GlibString string) => Signal self (string -> IO ())
statusBarTextChanged = Signal (connect_GLIBSTRING__NONE "status_bar_text_changed")
editingBegan :: WebViewClass self => Signal self (IO ())
editingBegan = Signal (connect_NONE__NONE "editing_began")
editingEnded :: WebViewClass self => Signal self (IO ())
editingEnded = Signal (connect_NONE__NONE "editing_ended")
selectAll :: WebViewClass self => Signal self (IO ())
selectAll = Signal (connect_NONE__NONE "select_all")
selectionChanged :: WebViewClass self => Signal self (IO ())
selectionChanged = Signal (connect_NONE__NONE "selection_changed")
setScrollAdjustments :: WebViewClass self => Signal self (Adjustment -> Adjustment -> IO ())
setScrollAdjustments = Signal (connect_OBJECT_OBJECT__NONE "set_scroll_adjustments")
databaseQuotaExceeded :: WebViewClass self => Signal self (WebFrame -> WebDatabase -> IO ())
databaseQuotaExceeded = Signal (connect_OBJECT_OBJECT__NONE "database_quota_exceeded")
documentLoadFinished :: WebViewClass self => Signal self (WebFrame -> IO ())
documentLoadFinished = Signal (connect_OBJECT__NONE "document_load_finished")
webViewReady:: WebViewClass self => Signal self (IO Bool)
webViewReady =
    Signal (connect_NONE__BOOL "web_view_ready")
downloadRequested :: WebViewClass self => Signal self (Download -> IO Bool)
downloadRequested =
    Signal (connect_OBJECT__BOOL "download_requested")
iconLoaded :: (WebViewClass self, GlibString string) => Signal self (string -> IO ())
iconLoaded =
    Signal (connect_GLIBSTRING__NONE "icon_loaded")
redo :: WebViewClass self => Signal self (IO ())
redo = Signal (connect_NONE__NONE "redo")
undo :: WebViewClass self => Signal self (IO ())
undo = Signal (connect_NONE__NONE "undo")
mimeTypePolicyDecisionRequested :: (WebViewClass self, GlibString string) => Signal self (WebFrame -> NetworkRequest -> string -> WebPolicyDecision -> IO Bool)
mimeTypePolicyDecisionRequested = Signal (connect_OBJECT_OBJECT_GLIBSTRING_OBJECT__BOOL "mime_type_policy_decision_requested")
moveCursor :: WebViewClass self => Signal self (MovementStep -> Int -> IO Bool)
moveCursor = Signal (connect_ENUM_INT__BOOL "move_cursor")
navigationPolicyDecisionRequested :: WebViewClass self => Signal self (WebFrame -> NetworkRequest -> WebNavigationAction -> WebPolicyDecision -> IO Bool)
navigationPolicyDecisionRequested = Signal (connect_OBJECT_OBJECT_OBJECT_OBJECT__BOOL "navigation_policy_decision_requested")
newWindowPolicyDecisionRequested :: WebViewClass self => Signal self (WebFrame -> NetworkRequest -> WebNavigationAction -> WebPolicyDecision -> IO Bool)
newWindowPolicyDecisionRequested = Signal (connect_OBJECT_OBJECT_OBJECT_OBJECT__BOOL "new_window_policy_decision_requested")
resourceRequestStarting :: WebViewClass self => Signal self (WebFrame -> WebResource -> Maybe NetworkRequest -> Maybe NetworkResponse -> IO ())
resourceRequestStarting = Signal (connect_OBJECT_OBJECT_MOBJECT_MOBJECT__NONE "resource_request_starting")
geolocationPolicyDecisionCancelled :: WebViewClass self => Signal self (WebFrame -> IO ())
geolocationPolicyDecisionCancelled = Signal (connect_OBJECT__NONE "geolocation_policy_decision_cancelled")
geolocationPolicyDecisionRequested :: WebViewClass self => Signal self (WebFrame -> GeolocationPolicyDecision -> IO Bool)
geolocationPolicyDecisionRequested = Signal (connect_OBJECT_OBJECT__BOOL "geolocation_policy_decision_requested")
foreign import ccall safe "g_thread_get_initialized"
  g_thread_get_initialized :: (IO CInt)
foreign import ccall safe "g_thread_init"
  g_thread_init :: ((Ptr ()) -> (IO ()))
foreign import ccall safe "webkit_web_view_new"
  webkit_web_view_new :: (IO (Ptr Widget))
foreign import ccall safe "webkit_web_view_set_settings"
  webkit_web_view_set_settings :: ((Ptr WebView) -> ((Ptr WebSettings) -> (IO ())))
foreign import ccall safe "webkit_web_view_get_settings"
  webkit_web_view_get_settings :: ((Ptr WebView) -> (IO (Ptr WebSettings)))
foreign import ccall safe "webkit_web_view_get_window_features"
  webkit_web_view_get_window_features :: ((Ptr WebView) -> (IO (Ptr WebWindowFeatures)))
foreign import ccall safe "webkit_web_view_get_icon_uri"
  webkit_web_view_get_icon_uri :: ((Ptr WebView) -> (IO (Ptr CChar)))
foreign import ccall safe "webkit_web_view_try_get_favicon_pixbuf"
  webkit_web_view_try_get_favicon_pixbuf :: ((Ptr WebView) -> (CUInt -> (CUInt -> (IO (Ptr Pixbuf)))))
foreign import ccall safe "webkit_web_view_get_main_frame"
  webkit_web_view_get_main_frame :: ((Ptr WebView) -> (IO (Ptr WebFrame)))
foreign import ccall safe "webkit_web_view_get_focused_frame"
  webkit_web_view_get_focused_frame :: ((Ptr WebView) -> (IO (Ptr WebFrame)))
foreign import ccall safe "webkit_web_view_load_uri"
  webkit_web_view_load_uri :: ((Ptr WebView) -> ((Ptr CChar) -> (IO ())))
foreign import ccall safe "webkit_web_view_can_go_back"
  webkit_web_view_can_go_back :: ((Ptr WebView) -> (IO CInt))
foreign import ccall safe "webkit_web_view_can_go_forward"
  webkit_web_view_can_go_forward :: ((Ptr WebView) -> (IO CInt))
foreign import ccall safe "webkit_web_view_go_back"
  webkit_web_view_go_back :: ((Ptr WebView) -> (IO ()))
foreign import ccall safe "webkit_web_view_go_forward"
  webkit_web_view_go_forward :: ((Ptr WebView) -> (IO ()))
foreign import ccall safe "webkit_web_view_set_maintains_back_forward_list"
  webkit_web_view_set_maintains_back_forward_list :: ((Ptr WebView) -> (CInt -> (IO ())))
foreign import ccall safe "webkit_web_view_get_back_forward_list"
  webkit_web_view_get_back_forward_list :: ((Ptr WebView) -> (IO (Ptr WebBackForwardList)))
foreign import ccall safe "webkit_web_view_go_to_back_forward_item"
  webkit_web_view_go_to_back_forward_item :: ((Ptr WebView) -> ((Ptr WebHistoryItem) -> (IO CInt)))
foreign import ccall safe "webkit_web_view_can_go_back_or_forward"
  webkit_web_view_can_go_back_or_forward :: ((Ptr WebView) -> (CInt -> (IO CInt)))
foreign import ccall safe "webkit_web_view_go_back_or_forward"
  webkit_web_view_go_back_or_forward :: ((Ptr WebView) -> (CInt -> (IO ())))
foreign import ccall safe "webkit_web_view_can_redo"
  webkit_web_view_can_redo :: ((Ptr WebView) -> (IO CInt))
foreign import ccall safe "webkit_web_view_can_undo"
  webkit_web_view_can_undo :: ((Ptr WebView) -> (IO CInt))
foreign import ccall safe "webkit_web_view_redo"
  webkit_web_view_redo :: ((Ptr WebView) -> (IO ()))
foreign import ccall safe "webkit_web_view_undo"
  webkit_web_view_undo :: ((Ptr WebView) -> (IO ()))
foreign import ccall safe "webkit_web_view_can_show_mime_type"
  webkit_web_view_can_show_mime_type :: ((Ptr WebView) -> ((Ptr CChar) -> (IO CInt)))
foreign import ccall safe "webkit_web_view_get_editable"
  webkit_web_view_get_editable :: ((Ptr WebView) -> (IO CInt))
foreign import ccall safe "webkit_web_view_set_editable"
  webkit_web_view_set_editable :: ((Ptr WebView) -> (CInt -> (IO ())))
foreign import ccall safe "webkit_web_view_get_view_source_mode"
  webkit_web_view_get_view_source_mode :: ((Ptr WebView) -> (IO CInt))
foreign import ccall safe "webkit_web_view_set_view_source_mode"
  webkit_web_view_set_view_source_mode :: ((Ptr WebView) -> (CInt -> (IO ())))
foreign import ccall safe "webkit_web_view_get_transparent"
  webkit_web_view_get_transparent :: ((Ptr WebView) -> (IO CInt))
foreign import ccall safe "webkit_web_view_set_transparent"
  webkit_web_view_set_transparent :: ((Ptr WebView) -> (CInt -> (IO ())))
foreign import ccall safe "webkit_web_view_get_inspector"
  webkit_web_view_get_inspector :: ((Ptr WebView) -> (IO (Ptr WebInspector)))
foreign import ccall safe "webkit_web_view_load_request"
  webkit_web_view_load_request :: ((Ptr WebView) -> ((Ptr NetworkRequest) -> (IO ())))
foreign import ccall safe "webkit_web_view_get_zoom_level"
  webkit_web_view_get_zoom_level :: ((Ptr WebView) -> (IO CFloat))
foreign import ccall safe "webkit_web_view_set_zoom_level"
  webkit_web_view_set_zoom_level :: ((Ptr WebView) -> (CFloat -> (IO ())))
foreign import ccall safe "webkit_web_view_load_html_string"
  webkit_web_view_load_html_string :: ((Ptr WebView) -> ((Ptr CChar) -> ((Ptr CChar) -> (IO ()))))
foreign import ccall safe "webkit_web_view_load_string"
  webkit_web_view_load_string :: ((Ptr WebView) -> ((Ptr CChar) -> ((Ptr CChar) -> ((Ptr CChar) -> ((Ptr CChar) -> (IO ()))))))
foreign import ccall safe "webkit_web_view_get_title"
  webkit_web_view_get_title :: ((Ptr WebView) -> (IO (Ptr CChar)))
foreign import ccall safe "webkit_web_view_get_uri"
  webkit_web_view_get_uri :: ((Ptr WebView) -> (IO (Ptr CChar)))
foreign import ccall safe "webkit_web_view_stop_loading"
  webkit_web_view_stop_loading :: ((Ptr WebView) -> (IO ()))
foreign import ccall safe "webkit_web_view_reload"
  webkit_web_view_reload :: ((Ptr WebView) -> (IO ()))
foreign import ccall safe "webkit_web_view_reload_bypass_cache"
  webkit_web_view_reload_bypass_cache :: ((Ptr WebView) -> (IO ()))
foreign import ccall safe "webkit_web_view_zoom_in"
  webkit_web_view_zoom_in :: ((Ptr WebView) -> (IO ()))
foreign import ccall safe "webkit_web_view_zoom_out"
  webkit_web_view_zoom_out :: ((Ptr WebView) -> (IO ()))
foreign import ccall safe "webkit_web_view_search_text"
  webkit_web_view_search_text :: ((Ptr WebView) -> ((Ptr CChar) -> (CInt -> (CInt -> (CInt -> (IO CInt))))))
foreign import ccall safe "webkit_web_view_mark_text_matches"
  webkit_web_view_mark_text_matches :: ((Ptr WebView) -> ((Ptr CChar) -> (CInt -> (CUInt -> (IO CUInt)))))
foreign import ccall safe "webkit_web_view_move_cursor"
  webkit_web_view_move_cursor :: ((Ptr WebView) -> (CInt -> (CInt -> (IO ()))))
foreign import ccall safe "webkit_web_view_unmark_text_matches"
  webkit_web_view_unmark_text_matches :: ((Ptr WebView) -> (IO ()))
foreign import ccall safe "webkit_web_view_set_highlight_text_matches"
  webkit_web_view_set_highlight_text_matches :: ((Ptr WebView) -> (CInt -> (IO ())))
foreign import ccall safe "webkit_web_view_execute_script"
  webkit_web_view_execute_script :: ((Ptr WebView) -> ((Ptr CChar) -> (IO ())))
foreign import ccall safe "webkit_web_view_can_cut_clipboard"
  webkit_web_view_can_cut_clipboard :: ((Ptr WebView) -> (IO CInt))
foreign import ccall safe "webkit_web_view_can_copy_clipboard"
  webkit_web_view_can_copy_clipboard :: ((Ptr WebView) -> (IO CInt))
foreign import ccall safe "webkit_web_view_can_paste_clipboard"
  webkit_web_view_can_paste_clipboard :: ((Ptr WebView) -> (IO CInt))
foreign import ccall safe "webkit_web_view_cut_clipboard"
  webkit_web_view_cut_clipboard :: ((Ptr WebView) -> (IO ()))
foreign import ccall safe "webkit_web_view_copy_clipboard"
  webkit_web_view_copy_clipboard :: ((Ptr WebView) -> (IO ()))
foreign import ccall safe "webkit_web_view_paste_clipboard"
  webkit_web_view_paste_clipboard :: ((Ptr WebView) -> (IO ()))
foreign import ccall safe "webkit_web_view_delete_selection"
  webkit_web_view_delete_selection :: ((Ptr WebView) -> (IO ()))
foreign import ccall safe "webkit_web_view_has_selection"
  webkit_web_view_has_selection :: ((Ptr WebView) -> (IO CInt))
foreign import ccall safe "webkit_web_view_select_all"
  webkit_web_view_select_all :: ((Ptr WebView) -> (IO ()))
foreign import ccall safe "webkit_web_view_get_full_content_zoom"
  webkit_web_view_get_full_content_zoom :: ((Ptr WebView) -> (IO CInt))
foreign import ccall safe "webkit_web_view_set_full_content_zoom"
  webkit_web_view_set_full_content_zoom :: ((Ptr WebView) -> (CInt -> (IO ())))
foreign import ccall safe "webkit_web_view_get_encoding"
  webkit_web_view_get_encoding :: ((Ptr WebView) -> (IO (Ptr CChar)))
foreign import ccall safe "webkit_web_view_set_custom_encoding"
  webkit_web_view_set_custom_encoding :: ((Ptr WebView) -> ((Ptr CChar) -> (IO ())))
foreign import ccall safe "webkit_web_view_get_custom_encoding"
  webkit_web_view_get_custom_encoding :: ((Ptr WebView) -> (IO (Ptr CChar)))
foreign import ccall safe "webkit_web_view_get_load_status"
  webkit_web_view_get_load_status :: ((Ptr WebView) -> (IO CInt))
foreign import ccall safe "webkit_web_view_get_progress"
  webkit_web_view_get_progress :: ((Ptr WebView) -> (IO CDouble))
foreign import ccall safe "webkit_web_view_get_copy_target_list"
  webkit_web_view_get_copy_target_list :: ((Ptr WebView) -> (IO (Ptr TargetList)))
foreign import ccall safe "webkit_web_view_get_paste_target_list"
  webkit_web_view_get_paste_target_list :: ((Ptr WebView) -> (IO (Ptr TargetList)))
foreign import ccall unsafe "webkit_load_status_get_type"
  webkit_load_status_get_type :: CULong
foreign import ccall safe "webkit_web_window_features_get_type"
  webkit_web_window_features_get_type :: CULong
foreign import ccall safe "gtk_im_context_get_type"
  gtk_im_context_get_type :: CULong
foreign import ccall safe "webkit_web_view_get_dom_document"
  webkit_web_view_get_dom_document :: ((Ptr WebView) -> (IO (Ptr Document)))