module Graphics.UI.Gtk.WebKit.DOM.StyleSheetList(
item,
getLength,
StyleSheetList,
castToStyleSheetList,
gTypeStyleSheetList,
StyleSheetListClass,
toStyleSheetList,
) where
import Prelude hiding (drop, error, print)
import Data.Typeable (Typeable)
import Foreign.Marshal (maybePeek, maybeWith)
import System.Glib.FFI (maybeNull, withForeignPtr, nullForeignPtr, Ptr, nullPtr, castPtr, Word, Int64, Word64, CChar(..), CInt(..), CUInt(..), CLong(..), CULong(..), CLLong(..), CULLong(..), CShort(..), CUShort(..), CFloat(..), CDouble(..), toBool, fromBool)
import System.Glib.UTFString (GlibString(..), readUTFString)
import Control.Applicative ((<$>))
import Control.Monad (void)
import Control.Monad.IO.Class (MonadIO(..))
import System.Glib.GError
import Graphics.UI.Gtk.WebKit.DOM.EventTargetClosures
import Graphics.UI.Gtk.WebKit.DOM.EventM
import Graphics.UI.Gtk.WebKit.Types
import Graphics.UI.Gtk.WebKit.DOM.Enums
item ::
(MonadIO m, StyleSheetListClass self) =>
self -> Word -> m (Maybe StyleSheet)
item self index
= liftIO
(maybeNull (makeNewGObject mkStyleSheet)
((\(StyleSheetList arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_style_sheet_list_item argPtr1 arg2)
(toStyleSheetList self)
(fromIntegral index)))
getLength ::
(MonadIO m, StyleSheetListClass self) => self -> m Word
getLength self
= liftIO
(fromIntegral <$>
((\(StyleSheetList arg1) -> withForeignPtr arg1 $ \argPtr1 ->webkit_dom_style_sheet_list_get_length argPtr1)
(toStyleSheetList self)))
foreign import ccall safe "webkit_dom_style_sheet_list_item"
webkit_dom_style_sheet_list_item :: ((Ptr StyleSheetList) -> (CULong -> (IO (Ptr StyleSheet))))
foreign import ccall safe "webkit_dom_style_sheet_list_get_length"
webkit_dom_style_sheet_list_get_length :: ((Ptr StyleSheetList) -> (IO CULong))