module Graphics.UI.Gtk.WebKit.DOM.HTMLDirectoryElement
(htmlDirectoryElementSetCompact, htmlDirectoryElementGetCompact,
HTMLDirectoryElement, HTMLDirectoryElementClass,
castToHTMLDirectoryElement, gTypeHTMLDirectoryElement,
toHTMLDirectoryElement)
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
htmlDirectoryElementSetCompact ::
(HTMLDirectoryElementClass self) => self -> Bool -> IO ()
htmlDirectoryElementSetCompact self val
= (\(HTMLDirectoryElement arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_html_directory_element_set_compact argPtr1 arg2)
(toHTMLDirectoryElement self)
(fromBool val)
htmlDirectoryElementGetCompact ::
(HTMLDirectoryElementClass self) => self -> IO Bool
htmlDirectoryElementGetCompact self
= toBool <$>
((\(HTMLDirectoryElement arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_html_directory_element_get_compact argPtr1)
(toHTMLDirectoryElement self))
foreign import ccall safe "webkit_dom_html_directory_element_set_compact"
webkit_dom_html_directory_element_set_compact :: ((Ptr HTMLDirectoryElement) -> (CInt -> (IO ())))
foreign import ccall safe "webkit_dom_html_directory_element_get_compact"
webkit_dom_html_directory_element_get_compact :: ((Ptr HTMLDirectoryElement) -> (IO CInt))