module Graphics.UI.Gtk.WebKit.DOM.Console
(consoleTime, consoleGroupEnd, Console, ConsoleClass,
castToConsole, gTypeConsole, toConsole)
where
import System.Glib.FFI
import System.Glib.UTFString
import Control.Applicative
import Graphics.UI.Gtk.WebKit.Types
import System.Glib.GError
import Graphics.UI.Gtk.WebKit.DOM.EventM
consoleTime ::
(ConsoleClass self, GlibString string) => self -> string -> IO ()
consoleTime self title
= withUTFString title $
\ titlePtr ->
(\(Console arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_console_time argPtr1 arg2) (toConsole self) titlePtr
consoleGroupEnd :: (ConsoleClass self) => self -> IO ()
consoleGroupEnd self
= (\(Console arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_console_group_end argPtr1) (toConsole self)
foreign import ccall safe "webkit_dom_console_time"
webkit_dom_console_time :: ((Ptr Console) -> ((Ptr CChar) -> (IO ())))
foreign import ccall safe "webkit_dom_console_group_end"
webkit_dom_console_group_end :: ((Ptr Console) -> (IO ()))