module Graphics.UI.Gtk.WebKit.DOM.HTMLTableSectionElement
(htmlTableSectionElementInsertRow,
htmlTableSectionElementDeleteRow, htmlTableSectionElementSetAlign,
htmlTableSectionElementGetAlign, htmlTableSectionElementSetCh,
htmlTableSectionElementGetCh, htmlTableSectionElementSetChOff,
htmlTableSectionElementGetChOff, htmlTableSectionElementSetVAlign,
htmlTableSectionElementGetVAlign, htmlTableSectionElementGetRows,
HTMLTableSectionElement, HTMLTableSectionElementClass,
castToHTMLTableSectionElement, gTypeHTMLTableSectionElement,
toHTMLTableSectionElement)
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
htmlTableSectionElementInsertRow ::
(HTMLTableSectionElementClass self) =>
self -> Int -> IO (Maybe HTMLElement)
htmlTableSectionElementInsertRow self index
= maybeNull (makeNewGObject mkHTMLElement)
(propagateGError $
\ errorPtr_ ->
(\(HTMLTableSectionElement arg1) arg2 arg3 -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_html_table_section_element_insert_row argPtr1 arg2 arg3)
(toHTMLTableSectionElement self)
(fromIntegral index)
errorPtr_)
htmlTableSectionElementDeleteRow ::
(HTMLTableSectionElementClass self) => self -> Int -> IO ()
htmlTableSectionElementDeleteRow self index
= propagateGError $
\ errorPtr_ ->
(\(HTMLTableSectionElement arg1) arg2 arg3 -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_html_table_section_element_delete_row argPtr1 arg2 arg3)
(toHTMLTableSectionElement self)
(fromIntegral index)
errorPtr_
htmlTableSectionElementSetAlign ::
(HTMLTableSectionElementClass self, GlibString string) =>
self -> string -> IO ()
htmlTableSectionElementSetAlign self val
= withUTFString val $
\ valPtr ->
(\(HTMLTableSectionElement arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_html_table_section_element_set_align argPtr1 arg2)
(toHTMLTableSectionElement self)
valPtr
htmlTableSectionElementGetAlign ::
(HTMLTableSectionElementClass self, GlibString string) =>
self -> IO string
htmlTableSectionElementGetAlign self
= ((\(HTMLTableSectionElement arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_html_table_section_element_get_align argPtr1)
(toHTMLTableSectionElement self))
>>=
readUTFString
htmlTableSectionElementSetCh ::
(HTMLTableSectionElementClass self, GlibString string) =>
self -> string -> IO ()
htmlTableSectionElementSetCh self val
= withUTFString val $
\ valPtr ->
(\(HTMLTableSectionElement arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_html_table_section_element_set_ch argPtr1 arg2)
(toHTMLTableSectionElement self)
valPtr
htmlTableSectionElementGetCh ::
(HTMLTableSectionElementClass self, GlibString string) =>
self -> IO string
htmlTableSectionElementGetCh self
= ((\(HTMLTableSectionElement arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_html_table_section_element_get_ch argPtr1)
(toHTMLTableSectionElement self))
>>=
readUTFString
htmlTableSectionElementSetChOff ::
(HTMLTableSectionElementClass self, GlibString string) =>
self -> string -> IO ()
htmlTableSectionElementSetChOff self val
= withUTFString val $
\ valPtr ->
(\(HTMLTableSectionElement arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_html_table_section_element_set_ch_off argPtr1 arg2)
(toHTMLTableSectionElement self)
valPtr
htmlTableSectionElementGetChOff ::
(HTMLTableSectionElementClass self, GlibString string) =>
self -> IO string
htmlTableSectionElementGetChOff self
= ((\(HTMLTableSectionElement arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_html_table_section_element_get_ch_off argPtr1)
(toHTMLTableSectionElement self))
>>=
readUTFString
htmlTableSectionElementSetVAlign ::
(HTMLTableSectionElementClass self, GlibString string) =>
self -> string -> IO ()
htmlTableSectionElementSetVAlign self val
= withUTFString val $
\ valPtr ->
(\(HTMLTableSectionElement arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_html_table_section_element_set_v_align argPtr1 arg2)
(toHTMLTableSectionElement self)
valPtr
htmlTableSectionElementGetVAlign ::
(HTMLTableSectionElementClass self, GlibString string) =>
self -> IO string
htmlTableSectionElementGetVAlign self
= ((\(HTMLTableSectionElement arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_html_table_section_element_get_v_align argPtr1)
(toHTMLTableSectionElement self))
>>=
readUTFString
htmlTableSectionElementGetRows ::
(HTMLTableSectionElementClass self) =>
self -> IO (Maybe HTMLCollection)
htmlTableSectionElementGetRows self
= maybeNull (makeNewGObject mkHTMLCollection)
((\(HTMLTableSectionElement arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_html_table_section_element_get_rows argPtr1)
(toHTMLTableSectionElement self))
foreign import ccall safe "webkit_dom_html_table_section_element_insert_row"
webkit_dom_html_table_section_element_insert_row :: ((Ptr HTMLTableSectionElement) -> (CLong -> ((Ptr (Ptr ())) -> (IO (Ptr HTMLElement)))))
foreign import ccall safe "webkit_dom_html_table_section_element_delete_row"
webkit_dom_html_table_section_element_delete_row :: ((Ptr HTMLTableSectionElement) -> (CLong -> ((Ptr (Ptr ())) -> (IO ()))))
foreign import ccall safe "webkit_dom_html_table_section_element_set_align"
webkit_dom_html_table_section_element_set_align :: ((Ptr HTMLTableSectionElement) -> ((Ptr CChar) -> (IO ())))
foreign import ccall safe "webkit_dom_html_table_section_element_get_align"
webkit_dom_html_table_section_element_get_align :: ((Ptr HTMLTableSectionElement) -> (IO (Ptr CChar)))
foreign import ccall safe "webkit_dom_html_table_section_element_set_ch"
webkit_dom_html_table_section_element_set_ch :: ((Ptr HTMLTableSectionElement) -> ((Ptr CChar) -> (IO ())))
foreign import ccall safe "webkit_dom_html_table_section_element_get_ch"
webkit_dom_html_table_section_element_get_ch :: ((Ptr HTMLTableSectionElement) -> (IO (Ptr CChar)))
foreign import ccall safe "webkit_dom_html_table_section_element_set_ch_off"
webkit_dom_html_table_section_element_set_ch_off :: ((Ptr HTMLTableSectionElement) -> ((Ptr CChar) -> (IO ())))
foreign import ccall safe "webkit_dom_html_table_section_element_get_ch_off"
webkit_dom_html_table_section_element_get_ch_off :: ((Ptr HTMLTableSectionElement) -> (IO (Ptr CChar)))
foreign import ccall safe "webkit_dom_html_table_section_element_set_v_align"
webkit_dom_html_table_section_element_set_v_align :: ((Ptr HTMLTableSectionElement) -> ((Ptr CChar) -> (IO ())))
foreign import ccall safe "webkit_dom_html_table_section_element_get_v_align"
webkit_dom_html_table_section_element_get_v_align :: ((Ptr HTMLTableSectionElement) -> (IO (Ptr CChar)))
foreign import ccall safe "webkit_dom_html_table_section_element_get_rows"
webkit_dom_html_table_section_element_get_rows :: ((Ptr HTMLTableSectionElement) -> (IO (Ptr HTMLCollection)))