module Graphics.UI.Gtk.WebKit.DOM.StyleSheet
       (styleSheetSetDisabled, styleSheetGetDisabled,
        styleSheetGetOwnerNode, styleSheetGetParentStyleSheet,
        styleSheetGetHref, styleSheetGetTitle, styleSheetGetMedia,
        StyleSheet, StyleSheetClass, castToStyleSheet, gTypeStyleSheet,
        toStyleSheet)
       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
 
styleSheetSetDisabled ::
                      (StyleSheetClass self) => self -> Bool -> IO ()
styleSheetSetDisabled self val
  = (\(StyleSheet arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_style_sheet_set_disabled argPtr1 arg2)
      (toStyleSheet self)
      (fromBool val)
 
styleSheetGetDisabled :: (StyleSheetClass self) => self -> IO Bool
styleSheetGetDisabled self
  = toBool <$>
      ((\(StyleSheet arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_style_sheet_get_disabled argPtr1)
         (toStyleSheet self))
 
styleSheetGetOwnerNode ::
                       (StyleSheetClass self) => self -> IO (Maybe Node)
styleSheetGetOwnerNode self
  = maybeNull (makeNewGObject mkNode)
      ((\(StyleSheet arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_style_sheet_get_owner_node argPtr1)
         (toStyleSheet self))
 
styleSheetGetParentStyleSheet ::
                              (StyleSheetClass self) => self -> IO (Maybe StyleSheet)
styleSheetGetParentStyleSheet self
  = maybeNull (makeNewGObject mkStyleSheet)
      ((\(StyleSheet arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_style_sheet_get_parent_style_sheet argPtr1)
         (toStyleSheet self))
 
styleSheetGetHref :: (StyleSheetClass self) => self -> IO String
styleSheetGetHref self
  = ((\(StyleSheet arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_style_sheet_get_href argPtr1) (toStyleSheet self))
      >>=
      readUTFString
 
styleSheetGetTitle :: (StyleSheetClass self) => self -> IO String
styleSheetGetTitle self
  = ((\(StyleSheet arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_style_sheet_get_title argPtr1) (toStyleSheet self))
      >>=
      readUTFString
 
styleSheetGetMedia ::
                   (StyleSheetClass self) => self -> IO (Maybe MediaList)
styleSheetGetMedia self
  = maybeNull (makeNewGObject mkMediaList)
      ((\(StyleSheet arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_style_sheet_get_media argPtr1) (toStyleSheet self))
foreign import ccall safe "webkit_dom_style_sheet_set_disabled"
  webkit_dom_style_sheet_set_disabled :: ((Ptr StyleSheet) -> (CInt -> (IO ())))
foreign import ccall safe "webkit_dom_style_sheet_get_disabled"
  webkit_dom_style_sheet_get_disabled :: ((Ptr StyleSheet) -> (IO CInt))
foreign import ccall safe "webkit_dom_style_sheet_get_owner_node"
  webkit_dom_style_sheet_get_owner_node :: ((Ptr StyleSheet) -> (IO (Ptr Node)))
foreign import ccall safe "webkit_dom_style_sheet_get_parent_style_sheet"
  webkit_dom_style_sheet_get_parent_style_sheet :: ((Ptr StyleSheet) -> (IO (Ptr StyleSheet)))
foreign import ccall safe "webkit_dom_style_sheet_get_href"
  webkit_dom_style_sheet_get_href :: ((Ptr StyleSheet) -> (IO (Ptr CChar)))
foreign import ccall safe "webkit_dom_style_sheet_get_title"
  webkit_dom_style_sheet_get_title :: ((Ptr StyleSheet) -> (IO (Ptr CChar)))
foreign import ccall safe "webkit_dom_style_sheet_get_media"
  webkit_dom_style_sheet_get_media :: ((Ptr StyleSheet) -> (IO (Ptr MediaList)))