-- GENERATED by C->Haskell Compiler, version 0.13.13 (gtk2hs branch) "Bin IO", 27 May 2012 (Haskell)
-- Edit the ORIGNAL .chs file instead!


{-# LINE 1 "./Graphics/UI/Gtk/WebKit/DOM/StyleSheetList.chs" #-}
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
{-# LINE 21 "./Graphics/UI/Gtk/WebKit/DOM/StyleSheetList.chs" #-}
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)
{-# LINE 31 "./Graphics/UI/Gtk/WebKit/DOM/StyleSheetList.chs" #-}
            (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)
{-# LINE 40 "./Graphics/UI/Gtk/WebKit/DOM/StyleSheetList.chs" #-}
            (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))