module Graphics.UI.Gtk.WebKit.WebInspector (
WebInspector,
WebInspectorClass,
webInspectorGetInspectedUri,
webInspectorGetWebView,
webInspectorInspectCoordinates,
webInspectorShow,
webInspectorClose,
webInspectorInspectedUri,
webInspectorJSProfilingEnable,
webInspectorTimelineProfilingEnabled,
webInspectorWebView,
attachWindow,
detachWindow,
closeWindow,
showWindow,
finished,
inspectWebView,
) where
import Control.Monad (liftM)
import System.Glib.FFI
import System.Glib.UTFString
import System.Glib.GList
import System.Glib.GError
import System.Glib.Attributes
import System.Glib.Properties
import Graphics.UI.Gtk.Gdk.Events
import Graphics.UI.Gtk.Abstract.Object (makeNewObject)
import Graphics.UI.Gtk.WebKit.Types
import Graphics.UI.Gtk.WebKit.Internal
import Graphics.UI.Gtk.WebKit.Signals
import System.Glib.GObject
webInspectorGetInspectedUri ::
WebInspectorClass self => self
-> IO String
webInspectorGetInspectedUri inspector =
(\(WebInspector arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_web_inspector_get_inspected_uri argPtr1) (toWebInspector inspector) >>= peekCString
webInspectorGetWebView ::
WebInspectorClass self => self
-> IO (Maybe WebView)
webInspectorGetWebView inspector =
maybeNull (makeNewObject mkWebView) $ liftM castPtr $
(\(WebInspector arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_web_inspector_get_web_view argPtr1)
(toWebInspector inspector)
webInspectorInspectCoordinates :: WebInspectorClass self
=> self
-> Int
-> Int
-> IO ()
webInspectorInspectCoordinates inspect x y =
(\(WebInspector arg1) arg2 arg3 -> withForeignPtr arg1 $ \argPtr1 ->webkit_web_inspector_inspect_coordinates argPtr1 arg2 arg3)
(toWebInspector inspect)
(fromIntegral x)
(fromIntegral y)
webInspectorShow :: WebInspectorClass self => self -> IO ()
webInspectorShow inspect =
(\(WebInspector arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_web_inspector_show argPtr1) (toWebInspector inspect)
webInspectorClose :: WebInspectorClass self => self -> IO ()
webInspectorClose inspect =
(\(WebInspector arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_web_inspector_close argPtr1) (toWebInspector inspect)
webInspectorInspectedUri :: (WebInspectorClass self) => ReadAttr self String
webInspectorInspectedUri = readAttr webInspectorGetInspectedUri
webInspectorJSProfilingEnable :: (WebInspectorClass self) => Attr self Bool
webInspectorJSProfilingEnable = newAttrFromBoolProperty "javascript-profiling-enabled"
webInspectorTimelineProfilingEnabled :: (WebInspectorClass self) => Attr self Bool
webInspectorTimelineProfilingEnabled = newAttrFromBoolProperty "timeline-profiling-enabled"
webInspectorWebView :: (WebInspectorClass self) => ReadAttr self WebView
webInspectorWebView =
readAttrFromObjectProperty "web-view"
webkit_web_view_get_type
attachWindow :: WebInspectorClass self => Signal self (IO Bool)
attachWindow = Signal (connect_NONE__BOOL "attach-window")
detachWindow :: WebInspectorClass self => Signal self (IO Bool)
detachWindow = Signal (connect_NONE__BOOL "detach-window")
closeWindow :: WebInspectorClass self => Signal self (IO Bool)
closeWindow = Signal (connect_NONE__BOOL "close-window")
showWindow :: WebInspectorClass self => Signal self (IO Bool)
showWindow = Signal (connect_NONE__BOOL "show-window")
finished :: WebInspectorClass self => Signal self (IO ())
finished = Signal (connect_NONE__NONE "finished")
inspectWebView :: WebInspectorClass self => Signal self (WebView -> IO WebView)
inspectWebView = Signal (connect_OBJECT__OBJECTPTR "inspect-web-view")
foreign import ccall safe "webkit_web_inspector_get_inspected_uri"
webkit_web_inspector_get_inspected_uri :: ((Ptr WebInspector) -> (IO (Ptr CChar)))
foreign import ccall safe "webkit_web_inspector_get_web_view"
webkit_web_inspector_get_web_view :: ((Ptr WebInspector) -> (IO (Ptr WebView)))
foreign import ccall safe "webkit_web_inspector_inspect_coordinates"
webkit_web_inspector_inspect_coordinates :: ((Ptr WebInspector) -> (CDouble -> (CDouble -> (IO ()))))
foreign import ccall safe "webkit_web_inspector_show"
webkit_web_inspector_show :: ((Ptr WebInspector) -> (IO ()))
foreign import ccall safe "webkit_web_inspector_close"
webkit_web_inspector_close :: ((Ptr WebInspector) -> (IO ()))
foreign import ccall safe "webkit_web_view_get_type"
webkit_web_view_get_type :: CUInt